home *** CD-ROM | disk | FTP | other *** search
- page 66,132
- ;============================================================================
- ; PCMKEY adds a command line stack, a command line editor, and
- ; an alias function to COMMAND.COM.
- ;
- ; PCMKEY.ASM Copyright 1990 Doug Boling and Jeff Prosise
- ; Copyright 1994 Douglas Boling
- ;
- ;============================================================================
- MAXKEYS equ 64
- STACKSIZE equ 256
- RES_STACK equ offset end_of_resident + STACKSIZE
- INSTDATASIZE equ offset DataBlockEnd - offset DataBlock
-
- code segment
- assume cs:code
-
- org 2ch
- env_segment dw ? ;Word containing the segment
- ; of the program's env. block.
- org 80h
- command_tail db ? ;Offset of the command tail.
-
- org 100h
-
- main: jmp initialize
- program db 13,10,"PCMKEY 1.0 "
- copyright db "Copyright 1990 Doug Boling and Jeff Prosise",10,13
- db "Copyright 1994 Douglas Boling",10,13
- db "Published in PC Magazine, November 22, 1994"
- endmsg db 13,10,0,1Ah
-
- pick_prompt db 11,"Cmd number:"
- pick_prompt_end = $
-
- dos_version dw 0 ;DOS Version number
- win_enhanced db 0
- temp_buff dd ? ;Addr of temp buffer
- work_buff_ptr dw ? ;Pointer to alias working buff
- ;
- ;Switcher global data structures
- ;
- StartupInfo = $
- sisVersion dw 3 ;Switcher structure ID
- sisNextDev dd 0 ;Ptr to prev startup structure
- sisVirtDevFile dd 0 ;Ptr to name of opt dev drvr
- sisReferenceData dd 0 ;Data for Win dev drivr
- sisInstData dd 0 ;Ptr to instance mem list
-
- DataBlockPtr dd 0 ;Ptr to instance data
- DataBlockSize dw 0 ;Size of instance data
- StackBlockPtr dd 0 ;Ptr to instance stack
- StackBlockSize dw 0 ;Size of instance stack
- TempBlockPtr dd 0 ;Ptr to temp buffer
- TempBlockSize dw 128 ;Size of temp buffer
- dd 0 ;Ptr to next block = 0 to
- dw 0 ; terminate list
- ;
- ; Instance data
- ;
- DataBlock = $
- aliaslist_ptr dd ? ;Pointer to alias list.
- aliaslist_size dw ? ;Pointer to end of list seg
-
- chk_alias db 1 ;Alias enable flag.
- minlength db 1 ;Minimum len of cmd to stack
- cmdcom_env dw 0 ;Segment of master environment
-
- saved_ss dw ?
- saved_sp dw ?
- int21h dd -1 ;Int 21 vector (DOS)
- int2fh dd -1 ;Int 2f vector (DOS MULTIPLEX)
-
- multiplex_id db 0dbh ;Program ID for multiplex int
- last_click db 0 ;Used by GetKey routine
- ;
- ; Cmd line code vars
- ;
- bufferptr db ? ;Input buffer pointer
- columns db ? ;Number of screen columns
- points dw ? ;Scan lines per character
- cursor_mode dw ? ;Cursor mode
- lesschars dw ? ;Count of chars deleted
- shiftcount dw ? ;Count of chars shifted
-
- chk_case db 0 ;1 = respect case in srches
- insert_cursor db 0 ;1 = block over - line ins.
- insert_flag db 0 ;0 = insert off, 1 = on
- multi_cmd db 0 ;Multi cmd flag
- multi_switch db 14h ;Multi cmd sep char
- keys_cnt dw 0
- keylist_base dw ? ;Ptr to key code list
- cmdlist_base dw ? ;Ptr to cmd list
-
- cmdstack_base dw ? ;Offset of cmd stack
- cmdstack_end dw ? ;Offset of cmd stack end
-
- cmdstack_headl = $
- cmdstack_head dw ? ;Offset of cmd stack last cmd
- cmdstack_seg dw ? ;segment of cmd stack buff
- cmdstack_curr dw ? ;Offset of cmd stack curr cmd
-
- cmdstack_size dw 512 ;Size of command stack.
- ; in command stack
- DataBlockEnd = $
- ;============================================================================
- ; DOSINT processes calls to interrupt 21h
- ;============================================================================
- dosint proc far
- assume cs:code,ds:nothing,es:nothing
- cmp ah,0ah ;Check for char input
- je dosint_1 ;If so, continue
- goto_dos:
- jmp cs:[int21h] ;else pass the call to DOS
- ;
- ;Compare the active PSP with COMMAND.COM PSP.
- ;
- dosint_1:
- push ax ;Save registers
- push bx
- push es
- mov ah,51h ;Get active PSP segment
- pushf
- call cs:[int21h]
-
- mov es,bx ;See if PSP is own parent.
- cmp bx,es:[16h]
- je dosint_2 ;Yes, take the call.
- goto_dos1:
- pop es
- pop bx ;Cleanup and goto DOS
- pop ax
- jmp short goto_dos
- dosint_2:
- cld ;Set direction flag
- mov cs:[saved_ss],ss ;Save SS:SP
- mov cs:[saved_sp],sp
- cli
- push cs ;Move to internal stack
- pop ss
- mov sp,RES_STACK
- sti
- push bp ;Save remaining registers.
- mov bp,sp ;Set up stack access
- push cx
- push dx
- push di
- push si
- push ds
- ;
- ;Find environment for COMMAND.COM.
- ;
- mov es,bx
- mov ax,es:[2ch] ;Get seg of master env
-
- dec ax
- mov es,ax
- cmp byte ptr es:[0],"M" ;See if valid memory block
- je dosint_21
- mov dx,bx ;Save COMMAND PSP segment
- dec bx ;Point back to mcb
- mov es,bx
-
- add bx,es:[3] ;Get size of memory block
- inc bx
- cmp es:[1],dx ;See if owned by CMD.COM
- je dosint_21
- pop ds
- pop si
- pop di
- pop dx
- pop cx
- jmp goto_dos1
- dosint_21:
- inc ax
- mov cs:[cmdcom_env],ax ;Save env
- cmp cs:multi_cmd,0 ;Check for pending multiple
- je dosint_211 ; command.
- push ds
- lds si,cs:[temp_buff] ;DS:SI = temp buff
- xor cx,cx
- mov cl,ds:[si] ;Get length of saved cmd
- push cx
- push si
- inc si
- call print_string ;Print saved cmd
- pop si
- pop cx
- pop es ;ES:DI = out buffer
- mov di,dx
- inc cx
- jmp dosint_71 ;Copy cmd to out buffer
- dosint_211:
- ;
- ;The call is from COMMAND.COM. Invoke line editor.
- ;
- push ds ;Save DS
- xor ax,ax ;Then zero it
- mov ds,ax
- mov ax,ds:[0485h] ;Get number of scan lines
- mov cs:[points],ax ;Record new number of scan
- mov ax,ds:[0460h] ; lines per character and
- mov cs:[cursor_mode],ax ; cursor mode
- pop ds ;Restore DS
-
- push dx
- call cmd_input ;Call line editor
- pop dx
-
- mov cx,cs:[cursor_mode] ;Set default cursor
- mov ah,1
- int 10h
-
- mov ax,cs:[cmdstack_head] ;Get head ptr
- mov cs:[cmdstack_curr],ax ;Reset curr cmd ptr
- cmp cs:[cmdstack_size],0
- je dosint_3
- mov si,dx ;Copy input buff ptr
- inc si ;Move past buffer size
- mov cl,ds:[si] ;Get cmd length
- cmp cl,cs:[minlength] ;See if long enough to sav
- jb dosint_3
- xor ch,ch
- call cmd_record ;Save cmd in stack
- call srch_stack ;See if cmd already in stk
- jc dosint_22
- jnz dosint_22
- call del_cmd ;If so, delete stacked cmd
- dosint_22:
- mov cs:[cmdstack_head],di ;Save new head ptr
- mov cs:[cmdstack_curr],di ;Reset curr cmd ptr
- ;
- ;Check for alias before returning to COMMAND.COM
- ;
- dosint_3:
- cmp cs:[chk_alias],0 ;See if alias translation
- je dosint_8 ; is enabled.
- mov si,dx ;Get pointer to input buffer
- inc si
- xor cx,cx
- or cl,ds:[si] ;Get length of buffer
- je dosint_8 ;If buffer empty, exit.
- inc si ;Point to 1st char in buffer
- push cs
- pop es ;Set ES to installed code.
- call searchalias ;See if an alias is found.
- jc dosint_8 ;No, exit.
- ;
- ;If alias found, copy it from alias list to internal buffer.
- ;
- mov si,di ;Load SI with alias pointer
- mov ax,es
- mov ds,ax ;Point DS to alias list seg
- xor cx,cx
- mov cl,ds:[si+3] ;Get size of alias
- call getalias ;Get alias from list
- ;
- ;Append remainder of command line to alias if no cmd line parameters were used.
- ;
- or dx,dx ;See if any command line
- jne dosint_6 ; parameters were used.
- push si ;Save pointer to buffer.
- push ds
- mov di,si
- add di,cx ;Point DI to end of alias
- mov dx,cx ;Save length of alias
- mov si,[bp-4] ;Point DS:SI to command.com
- mov ds,[bp-10] ; data buffer.
- xor cx,cx
- inc si
- mov cl,[si] ;Get length of command line.
- cmp ah,cl ;See if enough space in
- ja dosint_4 ; internal buffer. If not
- mov cl,ah ; copy only until buff full.
- dosint_4:
- inc si
- mov bl,1 ;Skip past alias.
- call scan4char
- jc dosint_5
- dec si ;Back up 1 char
- inc cx
- add dx,cx ;Add length of command line.
- rep movsb ;Copy command line
- dosint_5:
- mov cx,dx ;Restore length of command
- pop ds ;Restore pointer
- pop si
- ;
- ;Copy alias from internal buffer to COMMAND.COM data buffer.
- ;
- dosint_6:
- mov di,[bp-4] ;Point ES:DI to command.com
- mov es,[bp-10] ; data buffer.
- mov dx,di
- mov al,es:[di] ;Get size of data buffer
- dec al ;If alias longer than buffer,
- cmp al,cl ; copy only the enough
- ja dosint_7 ; characters to fill the
- xor cx,cx ; buffer.
- mov cl,al
- dosint_7:
- inc di ;Move DI past length bytes
- mov es:[di],cl ;Save length of command
- dosint_71:
- inc di
- rep movsb
- mov byte ptr es:[di],13 ;Append carriage return
- ;
- ;Check for multiple cmds on one line
- ;
- dosint_8:
- mov cs:[multi_cmd],0 ;Assume no multi cmd.
- mov ds,[bp-10] ;DS = out buff seg
-
- mov di,dx ;ES:DI - out buff
- push ds
- pop es
- inc di ;Move past buff size byte
- xor cx,cx
- mov cl,ds:[di] ;Get length
- jcxz dosint_exit ;If zero, skip
- mov bx,di ;Copy ptr to len byte
- inc di
- mov al,cs:[multi_switch] ;Scan for Ctrl-T
- repne scasb
- jne dosint_exit ;No multi cmd, exit.
- mov byte ptr ds:[di-1],13
- stc
- sbb ds:[bx],cl
- mov si,di
- les di,cs:[temp_buff]
- mov al,cl ;Save length of remainder.
- stosb
- rep movsb
- mov cs:[multi_cmd],1 ;Set multi cmd flag.
- dosint_exit:
- pop ds
- pop si
- pop di
- pop dx
- pop cx
- pop bp
- cli
- mov ss,cs:[saved_ss] ;Restore stack pointer
- mov sp,cs:[saved_sp]
- sti
- pop es
- pop bx
- pop ax
- iret ;Return to COMMAND.COM
- dosint endp
- ;----------------------------------------------------------------------------
- ; GETALIAS Copies an alias from the alias list while substituting any
- ; environment variables and command line parameters.
- ; Entry: DS:SI - pointer to alias
- ; Exit: DS:SI - pointer to buffer containing translated alias.
- ; AH - free space in buffer
- ; CX - length of the alias
- ;----------------------------------------------------------------------------
- getalias proc near
- mov di,work_buff_ptr ;Point DI to internal buffer
- xor ax,ax ;Point to command by adding
- or al,ds:[si+2] ; the size of the alias to
- jne alias_0
- mov al,2
- alias_0:
- add si,ax ; pointer to the entry.
- add si,4 ;Move past list data.
- mov ah,126 ;AH contains max size of buff
- xor dx,dx ;Clear flag for line params
- alias_1:
- lodsb ;Get byte from alias
- cmp al,"%" ;See if special character
- je alias_3 ;Yes, process special char.
- alias_2:
- stosb ;Store byte from alias
- dec ah ;Dec buffer size counter
- jz alias_6 ;If internal buffer full, done
- loop alias_1
- jmp short alias_6 ;If at end of alias, done
- ;
- ;A percent sign has been found indicating a 'soft' parameter.
- ;
- alias_3:
- lodsb
- dec cx
- cmp al,"%" ;If double %, include in one
- je alias_2 ; % in alias.
- mov bh,al ;If *, copy all of command
- cmp al,"*" ; line into alias.
- je alias_31 ;Copy and check to see if
- sub bh,"0" ; the next char is a number.
- jb alias_5 ; If so, assume a line
- cmp bh,9 ; parameter.
- ja alias_5
- alias_31:
- call sublineparam ;Substitute a line paramter
- inc dx ;Set parameter used flag
- alias_4:
- loop alias_1
- jmp short alias_6 ;If at end of alias, done
- alias_5:
- dec si ;Backup to 1st character
- inc cx
- call subenvvar ;Substitute an environment var
- loop alias_1
- alias_6:
- mov si,work_buff_ptr ;Point SI to internal buffer
- mov cx,di ;Compute size of completed
- sub cx,si ; alias.
- nop_cmd:
- ret
- getalias endp
-
- ;----------------------------------------------------------------------------
- ; SUBLINEPARAM substitutes a parameter from the command line into the alias.
- ; Entry: DS:SI - pointer to alias
- ; ES:DI - pointer to buffer to copy the line parameter
- ; AH - remaining space in the internal buffer
- ; BH - binary number of the line parameter
- ; CX - length of the alias
- ; Exit: ES:DI - pointer to byte after the parameter in the buffer
- ; DS:SI - pointer to the character after the line parameter number
- ; CX - remaining length of the alias
- ;----------------------------------------------------------------------------
- sublineparam proc near
- push cx
- push si
- push ds
- mov si,[bp-4] ;Get pointer to command.com
- mov ds,[bp-10] ; data buffer.
- xor cx,cx
- inc si ;Get number of chars in buffer.
- mov cl,ds:[si] ;Point to the first byte of
- inc si ; data.
- sublineparam_1:
- or bh,bh ;Check count of param to find.
- jz sublineparam_2
- mov bl,1
- call scan4char ;Find next space
- jc sublineparam_exit
- dec bl
- call scan4char ;Find next word
- jc sublineparam_exit
- cmp bh,'*'
- je sublineparam_11
- dec bh ;Dec parameter count
- jne sublineparam_1 ;If not done, loop back.
- sublineparam_11:
- dec si ;Backup to 1st char in word.
- sublineparam_2:
- lodsb ;Get character from parameter
- cmp bh,'*'
- je sublineparam_3
- cmp al,' ' ;If space, parameter done
- jbe sublineparam_exit
- sublineparam_3:
- cmp al,13 ;If CR, line done
- jbe sublineparam_exit
- stosb
- dec ah ;Dec buffer size counter
- jnz sublineparam_2
- sublineparam_exit:
- pop ds
- pop si
- pop cx
- ret
- sublineparam endp
-
- ;----------------------------------------------------------------------------
- ; SUBENVVAR substitutes an environment variable into alias.
- ; Entry: DS:SI - pointer to variable to substitute
- ; ES:DI - pointer to buffer to copy the contents of the variable
- ; AH - remaining space in internal buffer
- ; CX - length of alias string
- ; Exit: DS:SI - pointer to the byte after the variable name
- ; ES:DI - pointer to the byte after the variable contents
- ; CF - set if variable not found
- ;----------------------------------------------------------------------------
- subenvvar proc near
- push dx
- push ds
- push es
- ;
- ;Compute the length of the variable name.
- ;
- mov bx,di ;Save pointer to internal buff
- mov di,si ;Compute the length of the
- mov dx,cx ; environment variable by
- mov al,"%" ; searching for the trailing
- repne scasb ; % sign.
- je subenvvar_0
- mov di,bx ;If no trailing %, ignore
- mov cx,dx ; and continue.
- jmp short subenvvar_exit1
- subenvvar_0:
- sub dx,cx ;Compute length of variable.
- dec dx ;Subtract % byte fron length.
- push di ;Save ptr to end of env var.
- ;
- ;Search the Master Environment block for the variable pointed to by DS:SI
- ;
- mov es,cs:[cmdcom_env] ;Get segment of master env blk
- xor di,di ;Point ES:DI to environment.
- push cx ;Save alias size.
- push bx ;Save ptr to internal buffer
- mov bx,si ;Save pointer to var name
- subenvvar_1:
- mov si,bx ;Get back ptr to var name.
- mov cx,dx ;Compare env var to var in
- repe cmpsb ; alias.
- jne subenvvar_11 ;Variable not found.
- cmp byte ptr es:[di],'='
- je subenvvar_2 ;Variable found, exit loop
- subenvvar_11:
- xor al,al ;Find next environment var.
- mov cx,-1 ;Scan the entire segment.
- repne scasb
- cmp byte ptr es:[di],0 ;If double zero, end of env
- jne subenvvar_1 ; block. else, loop back.
- pop di ;Restore DI and exit
- jmp short subenvvar_exit
- ;
- ;Environment variable found. Substitute into alias.
- ;
- subenvvar_2:
- mov si,es ;DS:SI points to env string
- mov ds,si ;ES:DI points to internal buff
- mov si,cs
- mov es,si
- mov si,di ;Copy pointer to var contents.
- pop di ;Restore ptr to internal buff
- subenvvar_3:
- lodsb ;Move environment pointer past
- cmp al,"=" ; the equals sign.
- jne subenvvar_3
- subenvvar_4:
- lodsb ;Move pointer to first
- cmp al," " ; non-space character.
- jb subenvvar_4
- subenvvar_5:
- or al,al ;See if at the end of variable
- je subenvvar_exit
- stosb ;Save character in command
- lodsb ;Get next character
- dec ah ;Dec buffer size count.
- jne subenvvar_5 ;If buffer not full, continue
- subenvvar_exit:
- pop cx ;Restore alias length
- pop si ;Restore alias pointer
- subenvvar_exit1:
- pop es ;Restore segment registers
- pop ds
- pop dx
- ret
- subenvvar endp
-
- ;----------------------------------------------------------------------------
- ; SUBKEY searches the alias list for a key substitution
- ; Entry: AX - key code
- ; Exit: CF - clear if key found, set if not found
- ; DX - offset address of matching entry in alias list (if CF = 0)
- ; CX - length of matching entry (if CF = 0)
- ;----------------------------------------------------------------------------
- subkey proc near
- push bx
- push di
- push si
- push ds
- push es
- push cs
- pop es
- call searchkey ;Find key in alias list
- jc subkey_exit
- ;
- ;Copy alias into internal buffer.
- ;
- mov si,di ;Load SI with alias pointer
- mov ax,es
- mov ds,ax ;Point DS to alias list seg
- xor cx,cx
- mov cl,ds:[si+3] ;Get size of alias
- call getalias ;Get alias from list
- mov dx,si ;Copy pointer to buffer
- clc ;Set key found flag
- subkey_exit:
- pop es
- pop ds
- pop si
- pop di
- pop bx
- ret
- subkey endp
- ;-----------------------------------------------------------------------------
- ; SEARCHKEY searches the alias list for a matching key code.
- ; Entry: AX - keycode to search for
- ; ES - segment of installed code
- ; Exit: CF - clear if alias found
- ; ES:DI - pointer to matching entry in alias list, if CF is clear
- ;-----------------------------------------------------------------------------
- searchkey proc near
- les di,es:[aliaslist_ptr] ;Get pointer to alias list.
- searchkey_1:
- mov dx,es:[di] ;Get next entry offset
- cmp dx,-1 ;See if at the end of the list
- stc ;Set error flag (doesn't change
- je searchkey_exit ; JE test).
- cmp es:[di+4],ax ;Check for key code.
- je searchkey_exit ;If found, exit loop
- searchkey_2:
- add di,dx ;Else, point to next entry.
- jmp short searchkey_1
- searchkey_exit:
-
- ret
- searchkey endp
- ;-----------------------------------------------------------------------------
- ; SEARCHALIAS searches the alias list for a matching alias.
- ; Entry: DS:SI - pointer to alias
- ; ES - segment of installed code
- ; CX - length input buffer
- ; Exit: CF - clear if alias found
- ; ES:DI - pointer to matching entry in alias list, if CF is clear
- ;-----------------------------------------------------------------------------
- searchalias proc near
- push bx ;Save registers
- push cx
- push si
- xor bx,bx
- searchalias_1:
- lodsb ;Compute the length of the
- or al,al ; length of the alias by
- je searchalias_2 ; finding the next space.
- cmp al," " ;Allow zero byte in alias
- jbe searchalias_3 ; for function key labels.
- searchalias_2:
- inc bx
- loop searchalias_1
- searchalias_3:
- pop si
- les di,es:[aliaslist_ptr] ;Get pointer to alias list.
- mov cx,bx ;Get length of alias
- searchalias_4:
- mov bx,es:[di]
- cmp bx,-1 ;See if at the end of the list
- je searchalias_notfound
- cmp es:[di+2],cl ;Compare lengths
- jne searchalias_5
- push cx ;Save size and starting
- push di ; pointers.
- push si
- add di,4 ;Point to start of alias field.
- repe cmpsb ;Compare alias to input string
- pop si
- pop di
- pop cx
- je searchalias_6 ;If found, exit loop
- searchalias_5:
- add di,bx ;Else, point to next entry.
- jmp short searchalias_4
- searchalias_6:
- clc ;Set alias found flag
- searchalias_exit:
- pop cx
- pop bx
- ret
- searchalias_notfound:
- stc
- jmp short searchalias_exit
- searchalias endp
-
- ;-----------------------------------------------------------------------------
- ; SCAN4CHAR scans a string to find the first character.
- ; Entry: SI - pointer to ASCII string
- ; BL - 0 = find next char, 1 = find next space
- ; CX - file length
- ; Exit: AL - first nonspace character
- ; CF - set if carriage return found
- ;-----------------------------------------------------------------------------
- scan4char proc near
- assume ds:nothing,es:nothing
- scan4loop:
- jcxz scan4_eol ;See if at the end of the file.
- lodsb
- dec cx ;Decrement file length counter.
- cmp al,13 ;Check for carriage return.
- jne scan4_1
- scan4_eol:
- stc
- jmp short scan4_exit1
- scan4_1:
- or bl,bl ;Check if searching for space
- jne scan4_2 ; or character.
- cmp al," " ;Check for space or other
- jbe scan4loop ; 'white' characters.
- jmp short scan4_exit
- scan4_2:
- cmp al," " ;Check for characters.
- ja scan4loop
- scan4_exit:
- clc
- scan4_exit1:
- ret
- scan4char endp
-
- ;----------------------------------------------------------------------------
- ; CMD_INPUT replaces DOS' 0Ah text input function.
- ; Entry: DS:DX - Ptr to input buffer
- ;----------------------------------------------------------------------------
- cmd_input proc near
- call set_cursor ;Set cursor mode
-
- mov ah,15 ;Get video page and columns
- int 10h
- dec ah ;Calculate max column number
- mov cs:[columns],ah ;Save it
- mov ax,ds ;Point ES:DI to buffer
- les di,temp_buff
- mov byte ptr es:[di],0 ;Zero search buffer
- mov es,ax
- mov di,dx
- add di,2
- mov si,dx ;Point DS:SI to character cnt
- inc si
- mov byte ptr [si],0 ;Zero initial count
- mov cs:[bufferptr],1 ;Set initial index value
- ;
- ;Wait for a keycode to appear in the keyboard buffer.
- ;
- cmd_2:
- call getkey ;Read a key
- call srch4cmd ;See if key in cmd list. If
- jne cmd_3 ; not found, print it.
- call cx ;Call handling routine
- jmp short cmd_2 ;Return to input loop
- cmd_3:
- call printchar ;Call print char routine
- jmp short cmd_2 ;Return to input loop
- cmd_input endp
-
- ;----------------------------------------------------------------------------
- ; GETKEY Returns keycode and shift status from keyboard.
- ; Exit: AX - Keycode and shift status
- ;----------------------------------------------------------------------------
- getkey proc near
- push dx
- push di
- push es
- mov ax,40h ;BIOS data seg
- mov es,ax
- getkey_1:
- mov ah,6 ;Get keycode
- mov dl,0ffh
- int 21h
- jne getkey_2 ;Yes, then go get it
-
- mov al,es:[6dh] ;Get 2nd byte of timer ctr
- and al,0fch
- cmp al,cs:[last_click] ;See if same 64 second
- je getkey_11 ; incriment.
- mov cs:[last_click],al ;Every 16 seconds, call
- mov ah,2ch ; DOS Get Time. Do this
- int 21h ; to reset 24 hr flag.
- getkey_11:
- int 28h ;No, then execute int 28h
- cmp cs:win_enhanced,0
- je getkey_1
- mov ax,4680h ;Free timeslice
- int 2fh
- jmp short getkey_1 ;Loop back for another try
- getkey_2:
- xor ah,ah
- or al,al ;Is it an extended code?
- jne getkey_3 ;No, then branch
- mov ah,6 ;Yes, read extended char
- int 21h
- mov ah,80h ;Set ext char flag
- getkey_3:
- mov dl,es:[17h]
- test dl,3 ;If one shift key pressed,
- jz getkey_4 ; mark both.
- or dl,3
- getkey_4:
- and dl,0fh ;Look only at shift bits
- or ah,dl ;Combine shift with char
- pop es
- pop di
- pop dx
- ret
- getkey endp
- ;----------------------------------------------------------------------------
- ; SRCH4CMD Searchs the key list for matching key
- ; Entry: AX - Key code
- ; Exit: ZF - Set if key found
- ; CX - Offset of cmd routine if key found
- ;----------------------------------------------------------------------------
- srch4cmd proc near
- assume cs:code,ds:nothing
- push es
- push di
- push cs ;Point ES:DI to list of
- pop es ; supported keycodes
- mov di,keylist_base
- mov cx,keys_cnt
- repne scasw ;Scan list of keys.
- jne srch4cmd_exit
- not cx
- add cx,keys_cnt
- shl cx,1
- mov di,cx ;Get entry address from table
- add di,cmdlist_base
- mov cx,cs:[di]
- cmp ax,ax ;Set ZF
- srch4cmd_exit:
- pop di ;Clear the stack
- pop es
- ret
- srch4cmd endp
- ;----------------------------------------------------------------------------
- ; SHIFT_KEY Allows double key combinations
- ; Entry: DS:SI - input buffer address
- ;----------------------------------------------------------------------------
- shift_key proc near
- assume cs:code,ds:nothing
- shift1_key:
- mov ch,40h
- jmp short shift_key_1
- shift2_key:
- mov ch,20h
- jmp short shift_key_1
- shift3_key:
- mov ch,10h
- shift_key_1:
- call getkey ;Read a key
- or ah,ch ;Add shift component
- call srch4cmd
- jne shift_key_2 ;No match, exit
- jmp cx ;Jmp due to Enter cmd.
- shift_key_2:
- ret
- shift_key endp
- ;----------------------------------------------------------------------------
- ; ALIAS_STR displays an alias string in place of a key
- ; Entry: DS:SI - input buffer address
- ; AX - Key code entered
- ;----------------------------------------------------------------------------
- alias_str proc near
- assume cs:code,ds:nothing
- call subkey ;Scan alias list for match
- jc alias_str_exit ;Exit if no match found
- alias_str_1:
- push si
- mov si,dx ;Copy offset address into SI
- mov al,byte ptr cs:[si] ;Get next character
- pop si
- cmp al,13 ;If end of subparam is CR,
- jne alias_str_2 ; then exit and execute cmd.
- ;Don't push-pop params around this routine. The enter procedure does not
- ;return from its call!
- jmp enter
- alias_str_2:
- inc dx
- push cx
- push dx
- call printchar ;Print it
- pop dx
- pop cx
- jc alias_str_exit
- loop alias_str_1 ;Loop until done
- alias_str_exit:
- clc
- ret
- alias_str endp
- ;----------------------------------------------------------------------------
- ; PICK_STACK directly selects a stacked command by number
- ; Entry: DS:SI - input buffer address
- ;----------------------------------------------------------------------------
- pick_stack proc near
- push di
- push es
-
- push cs
- pop es
- mov di,offset pick_prompt ;Display prompt
- call write_command
- xor cx,cx
- pick_1:
- call getkey
- cmp al,13 ;Check for Enter
- je pick_2
- cmp al,27 ;Check for Esc
- je pick_11
- mov dl,al
- sub dl,30h ;Convert num from ASCII
- jb pick_1
- cmp dl,9
- ja pick_1
- push cx
- push dx
- call printchar
- pop dx
- pop cx
- mov al,10 ;CL = CL * 10 + DL
- mul cl
- mov cx,ax
- add cl,dl
- jmp short pick_1
- pick_11:
- xor cx,cx ;Clear number
- pick_2:
- push cx
- call clear_line
- pop cx
- jcxz pick_exit ;See if number = 0.
- mov es,cs:[cmdstack_seg] ;Get ptr to head of stack
- mov di,cs:[cmdstack_head]
- pick_3:
- call get_prev ;Get ptr to prev command
- cmp di,cs:[cmdstack_head] ;See if at end of list
- je pick_exit ;Yes, exit
- loop pick_3
- call write_command ;Copy cmd
- add sp,4 ;Keep new ES:DI
- jmp short pick_exit1
- pick_exit:
- pop es
- pop di
- pick_exit1:
- ret
- pick_stack endp
- ;----------------------------------------------------------------------------
- ; DUMP_STACK displays the contents of the command stack
- ; Entry: DS:SI - input buffer address
- ;----------------------------------------------------------------------------
- dump_stack proc near
- assume cs:code,ds:nothing
- push di
- push es
- mov es,cs:[cmdstack_seg] ;Get ptr to head of stack
- mov di,cs:[cmdstack_head]
- mov cx,1
- dump_stack_1:
- call get_prev ;Get ptr to prev command
- cmp di,cs:[cmdstack_head] ;See if at end of list
- je dump_stack_exit ;Yes, exit
- cmp byte ptr es:[di],0 ;See if no commands
- je dump_stack_exit ;Yes, exit
- call new_line
- mov ax,cx ;Print number
- call hex2asc
- mov al,':'
- call print_char
- mov al,' '
- call print_char
- push di
- inc di
- dump_stack_2:
- mov al,es:[di] ;Print stacked command
- inc di
- call chk_buffend
- or al,al
- je dump_stack_3
- call print_char
- jmp short dump_stack_2
- dump_stack_3:
- pop di
- inc cx
- jmp dump_stack_1
- dump_stack_exit:
- pop es
- pop di
- mov byte ptr ds:[si],0 ;Reset count
- lea di,[si+1] ;Reset char ptr
- jmp enter ;Force to get new prompt
- dump_stack endp
- ;----------------------------------------------------------------------------
- ; CLR_STACK empties the command stack.
- ; Entry: DS:SI - input buffer address
- ;----------------------------------------------------------------------------
- clr_stack proc near
- assume cs:code,ds:nothing
- push di
- push es
- mov es,cs:[cmdstack_seg] ;Get start of buffer
- mov di,cs:[cmdstack_base]
-
- mov cs:[cmdstack_head],di ;Reset pointers
- mov cs:[cmdstack_curr],di
-
- mov cx,cs:[cmdstack_size]
- xor ax,ax
- rep stosb ;Write zeros to buffer
- pop es
- pop di
- clc
- ret
- clr_stack endp
- ;----------------------------------------------------------------------------
- ; CLR_CMD clears the command line and resets the cmd stack ptr.
- ; Entry: DS:SI - input buffer address
- ;----------------------------------------------------------------------------
- clr_cmd proc near
- assume cs:code,ds:nothing
- call clear_line ;Clear cmd line
- push di
- mov di,cs:[cmdstack_head] ;Reset curr stack ptr
- mov cs:[cmdstack_curr],di
- pop di
- clc
- ret
- clr_cmd endp
- ;----------------------------------------------------------------------------
- ; CLR_ALIASES empties the alias buffer.
- ; Entry: DS:SI - input buffer address
- ;----------------------------------------------------------------------------
- clr_aliases proc near
- assume cs:code,ds:nothing
- push di
- push si
- push ds
- push es
- lds di,aliaslist_ptr
- push ds
- pop es
- clr_aliases_1:
- cmp word ptr ds:[di],-1 ;See if end of list
- je clr_aliases_3
- cmp byte ptr ds:[di+2],0 ;See if entry a key entry
- je clr_aliases_2
- push di
- call delete_aliasent ;No, delete it.
- pop di
- jmp short clr_aliases_1
- clr_aliases_2:
- add di,ds:[di] ;Point to next entry
- jmp short clr_aliases_1
- clr_aliases_3:
- clc
- pop es
- pop ds
- pop si
- pop di
- ret
- clr_aliases endp
- ;----------------------------------------------------------------------------
- ; BEEP_CMD attempts to beep the speaker
- ; Entry: DS:SI - input buffer address
- ;----------------------------------------------------------------------------
- beep_cmd proc near
- assume cs:code,ds:nothing
- mov ax,0e07h ;BIOS print char: BEEP
- int 10h
- ret
- beep_cmd endp
- ;----------------------------------------------------------------------------
- ; ABORT_CMD ends and editing call and returns a zero buffer.
- ; Entry: DS:SI - input buffer address
- ;----------------------------------------------------------------------------
- abort_cmd proc near
- assume cs:code,ds:nothing
- call clear_line ;Remove current cmd
- jmp enter ;Force return
- abort_cmd endp
- ;----------------------------------------------------------------------------
- ; PREV1_CMD outputs the previous command in the command stack.
- ; Entry: DS:SI - input buffer address
- ;----------------------------------------------------------------------------
- prev1_cmd proc near
- assume cs:code,ds:nothing
- mov cl,1
- jmp short prev_cmd_2nd_entry
- prev1_cmd endp
- ;----------------------------------------------------------------------------
- ; PREV_CMD outputs the previous matching command in the command stack.
- ; Entry: DS:SI - input buffer address
- ;----------------------------------------------------------------------------
- prev_cmd proc near
- assume cs:code,ds:nothing
- xor cx,cx
- prev_cmd_2nd_entry:
- push bp
- mov bp,sp
- sub sp,2
- mov [bp-2],cx
- cmp cs:[cmdstack_size],0 ;See if stack enabled
- je prev_cmd_exit1
- push di
- push es
- mov di,cs:[cmdstack_curr] ;See if at bottom of stack
- cmp di,cs:[cmdstack_head] ;If so, save cmd template
- jne prev_cmd_0
-
- push si ;If at bottom of list, save
- xor cx,cx ; search template.
- or cl,ds:[si]
- call cmd_record
- pop si
- prev_cmd_0:
- mov es,cs:[cmdstack_seg] ;Get ptr to head of stack
- mov di,cs:[cmdstack_curr]
- prev_cmd_1:
- call get_prev ;Get ptr to prev command
- cmp di,cs:[cmdstack_head] ;See if at end of list
- je prev_cmd_exit ;Yes, exit
- cmp byte ptr [bp-2],0
- jne prev_cmd_2
- call cmp_cmdlines ;No, see if cmd matches
- jne prev_cmd_1 ;No match, keep looking
- prev_cmd_2:
- mov cs:[cmdstack_curr],di ;Set new cmd stack ptr
- call write_command ;Match, copy cmd
- add sp,4
- jmp short prev_cmd_exit1
- prev_cmd_exit:
- pop es
- pop di
- prev_cmd_exit1:
- mov sp,bp
- pop bp
- ret
- prev_cmd endp
- ;----------------------------------------------------------------------------
- ; NEXT_CMD outputs the next command in the command stack.
- ; Entry: DS:SI - input buffer address
- ;----------------------------------------------------------------------------
- next_cmd proc near
- assume cs:code,ds:nothing
- push di
- push es
- cmp cs:[cmdstack_size],0 ;See if stack enabled
- je next_cmd_exit
- mov es,cs:[cmdstack_seg] ;Get ptr to head of stack
- mov di,cs:[cmdstack_curr]
- next_cmd_1:
- cmp di,cs:[cmdstack_head] ;See if at end of list
- je short next_cmd_2 ;Yes, exit
- call get_next
- call cmp_cmdlines ;No, see if cmd matches
- jne next_cmd_1 ;No match, keep looking
- next_cmd_2:
- mov cs:[cmdstack_curr],di ;Set new cmd stack ptr
- call write_command
- add sp,4 ;Keep ES:DI from write_cmd
- jmp short next_cmd_exit1 ; routine and exit.
- next_cmd_exit:
- pop es
- pop di
- next_cmd_exit1:
- ret
- next_cmd endp
- ;------------------------------------------------------------------------------
- ; TOGGLE_INS toggles the insert flag.
- ;------------------------------------------------------------------------------
- toggle_ins proc near
- xor cs:[insert_flag],1 ;Toggle insert flag
- call set_cursor ;Set cursor mode
- ret
- toggle_ins endp
- ;------------------------------------------------------------------------------
- ; ENTER Completes command and exits getkey loop
- ; Warning: This routine does *not* return to the routine that called it!
- ;------------------------------------------------------------------------------
- enter proc near
- call eol ;Place cursor at end-of-line
- mov al,13
- mov es:[di],al ;Insert carriage return code
- call print_char
- add sp,2 ;Pop off return to getkey
- ret
- enter endp
- ;------------------------------------------------------------------------------
- ; TAB tabs to the next tab boundary.
- ;------------------------------------------------------------------------------
- tab proc near
- mov al,cs:[bufferptr] ;Calculate number of
- dec al ; spaces to insert for
- xor ah,ah ; soft tab
- mov bl,8
- div bl
- mov cx,8
- sub cl,ah
- tab1:
- push cx ;Print spaces
- mov ax,32
- call printchar
- pop cx
- jc tab_exit
- loop tab1
- tab_exit:
- ret
- tab endp
-
- ;------------------------------------------------------------------------------
- ; BACKSPACE deletes the character left of the cursor.
- ;------------------------------------------------------------------------------
- backspace proc near
- cmp cs:[bufferptr],1 ;At beginning of command line?
- je bs_exit ;Yes, then ignore it
- mov cl,[si] ;Get count
- sub cl,cs:[bufferptr] ;Calculate distance to end-of-line
- inc cl
- xor ch,ch
- push cx ;Save it
- jcxz bs1 ;Branch if at end-of-line
- ;
- ;Shift all characters right of the cursor in the buffer one slot left.
- ;
- push si ;Save SI and DI
- push di
- mov si,di ;Position them for shifts
- dec di
- rep movsb ;Shift characters right of cursor
- pop di ;Restore registers
- pop si
- ;
- ;Display the new string and update input parameters.
- ;
- bs1:
- call move_left ;Move cursor left
- bs2:
- pop cx ;Retrieve shift count
- push si ;Save SI
- mov si,di ;Point SI to new part of string
- call print_string ;Print the new part
- mov al,32
- call print_char ;Blank the last character
- pop si ;Restore registers
- mov ah,2 ;Reset the cursor
- int 10h
- dec byte ptr [si] ;Decrement character count
- bs_exit:
- ret
- backspace endp
-
- ;------------------------------------------------------------------------------
- ; PRINTCHAR writes a new character to the input buffer and echoes it.
- ; Entry: AX - character to print
- ; Exit: CF clear if character printed
- ; CF set if buffer full
- ;------------------------------------------------------------------------------
- printchar proc near
- cmp ah,80h ;Don't print non-standard
- je print0 ; chars.
- cmp al,7fh
- je print0
- cmp al,20h ;Don't display control
- jae print01 ; chars.
- print0:
- mov al,4
- print01:
- cmp cs:[insert_flag],0 ;Insert state on?
- jne print3 ;Yes, then branch
- ;
- ;Print a character in overstrike mode.
- ;
- mov cl,[si] ;Get count
- cmp cl,cs:[bufferptr] ;End-of-line?
- jae print2 ;No, then branch
- mov cl,[si-1] ;Get maximum length
- sub cl,[si] ;Subtract current length
- cmp cl,1 ;Buffer full?
- je beep ;Yes, then branch
- print1:
- inc byte ptr [si] ;Increment count
- print2:
- stosb ;Deposit new character
- call print_char ;Then print it
- inc cs:[bufferptr] ;Advance buffer pointer
- print_exit:
- clc ;Clear CF and exit
- ret
- beep:
- mov ax,0E07h ;Print ASCII 7 thru BIOS
- int 10h
- stc
- ret
- ;
- ;Print a character in insert mode.
- ;
- print3:
- mov cl,[si-1] ;Get maximum length
- sub cl,[si] ;Subtract current count
- cmp cl,1 ;Buffer full?
- je beep ;Yes, then branch
- mov cl,[si] ;Get count
- cmp cl,cs:[bufferptr] ;End-of-line?
- jb print1 ;Yes, then branch
- sub cl,cs:[bufferptr] ;Calculate number of shifts
- inc cl
- xor ch,ch
- push cx ;Save shift count
- push si ;Save SI
- add di,cx ;Position DI to end-of-line
- mov si,di ;Position SI just before it
- dec si
- std ;Set DF for now
- rep movsb ;Make room for new character
- cld ;Clear DF
- pop si ;Restore SI
- mov es:[di],al ;Deposit new character
- mov ah,3 ;Get cursor position
- int 10h
- pop cx ;Retrieve shift count
- inc cx ;Increment it
- push dx ;Save cursor position
- push si ;Save SI
- mov si,di ;Point SI to current location
- call print_string ;Print new part of string
- pop si ;Restore SI and DX
- pop dx
- mov ah,2 ;Reset cursor position
- int 10h
- inc byte ptr [si] ;Add to character count
- call move_right ;Move cursor right
- jmp print_exit
- printchar endp
-
- ;------------------------------------------------------------------------------
- ; DELETE deletes the character at the cursor.
- ;------------------------------------------------------------------------------
- delete proc near
- mov cl,[si] ;Get count
- cmp cl,cs:[bufferptr] ;End-of-line?
- jb del2 ;Yes, then ignore keypress
- sub cl,cs:[bufferptr] ;Calculate number of shifts
- xor ch,ch ;Byte to word in CX
- push cx ;Save shift count
- jcxz del1 ;Branch if no shifts
- push si ;Save SI and DI
- push di
- mov si,di ;Position registers for shift
- inc si
- rep movsb ;Shift chars right of cursor
- pop di ;Restore registers
- pop si
- del1:
- mov ah,3 ;Get cursor position
- int 10h
- jmp bs2 ;Exit thru BACKSPACE routine
- del2:
- ret
- delete endp
-
- ;------------------------------------------------------------------------------
- ; CTRL_BS deletes the word at the cursor.
- ;------------------------------------------------------------------------------
- ctrl_bs proc near
- xor cx,cx ;Exit now if there is nothing
- or cl,[si] ; on the command line
- jnz cbs1
- cbs_exit:
- ret
- cbs1:
- cmp cs:[bufferptr],1 ;Exit if the cursor is at the
- je cbs3 ; at the end of the command
- cmp cl,cs:[bufferptr] ; line or if it is under a
- jb cbs_exit ; space; otherwise, move to
- cmp byte ptr [di],32 ; the beginning of the
- je cbs_exit ; current word
- cmp byte ptr [di-1],32
- je cbs3
- cbs2:
- push cx ;Save CX
- call ctrl_left ;Move to start of word
- pop cx ;Restore CX
- cbs3:
- inc cx ;Calculate max number of
- push cx ; characters to search
- mov dl,cs:[bufferptr] ; looking for the next
- xor dh,dh ; word or end-of-line
- sub cx,dx
- push di ;Save DI
- cbs4:
- inc di ;Search until DI addresses
- cmp byte ptr [di],32 ; either the first character
- je cbs5 ; in the next word or the
- cmp byte ptr [di-1],32 ; end of the command line
- je cbs6
- cbs5:
- loop cbs4
- cbs6:
- mov dx,di ;Save final value of DI
- pop di ;Restore DI
- pop cx ;Retrieve count
- mov cs:[lesschars],dx ;Calculate number of chars to
- sub cs:[lesschars],di ; be deleted
- sub cx,dx ;Then calculate how many chars
- add cx,si ; must be shifted
- mov cs:[shiftcount],cx
- jcxz cbs7 ;Branch if no shift
- push si ;Save registers
- push di
- mov si,dx ;Point DS:SI to next word
- rep movsb ;Delete current word
- pop di ;Restore registers
- pop si
- cbs7:
- mov cx,cs:[lesschars] ;Update character counter
- sub [si],cl ; in input buffer
- mov ah,3 ;Save the current cursor
- int 10h ; position on the stack
- push si ;Update the text on the
- mov si,di ; command line
- mov cx,cs:[shiftcount]
- call print_string
- pop si
- mov cx,cs:[lesschars]
- cbs8:
- mov al,32 ;Print as many spaces as
- call print_char ; there were characters
- loop cbs8 ; deleted
- mov ah,2 ;Restore cursor position
- int 10h ; and exit
- ret
- ctrl_bs endp
- ;------------------------------------------------------------------------------
- ; CTRL_END deletes command line text from the cursor to the end of the line.
- ;------------------------------------------------------------------------------
- ctrl_end proc near
- mov cl,[si] ;Exit if already at end
- cmp cl,cs:[bufferptr] ; of line
- jb ce_exit
- sub cl,cs:[bufferptr] ;Calculate number of chars
- xor ch,ch ; to be deleted
- inc cx
- sub [si],cl ;Update count in input buffer
- push cx
- mov ah,3 ;Get and save cursor position
- int 10h
- pop cx
- ce1:
- mov al,32 ;Print as many spaces as
- call print_char ; there are characters
- loop ce1 ; to delete
- mov ah,2 ;Reset cursor position
- int 10h
- ce_exit:
- ret
- ctrl_end endp
- ;------------------------------------------------------------------------------
- ; MOVE_LEFT moves the cursor one character left.
- ;------------------------------------------------------------------------------
- move_left proc near
- cmp cs:[bufferptr],1 ;At beginning of line?
- je left2 ;Yes, then ignore keypress
- mov ah,3 ;Get cursor position
- int 10h
- dec dl ;Decrement it by 1
- cmp dl,0FFh
- jne left1
- mov dl,cs:[columns] ;Decrement row number by 1
- dec dh ; if cursor wraps around
- left1:
- mov ah,2 ;Set new position
- int 10h
- dec di ;Decrement pointers
- dec cs:[bufferptr]
- left2:
- ret
- move_left endp
- ;------------------------------------------------------------------------------
- ; MOVE_RIGHT moves the cursor one character right.
- ;------------------------------------------------------------------------------
- move_right proc near
- mov cl,[si] ;Get count
- cmp cl,cs:[bufferptr] ;End-of-line?
- jb rt2 ;Yes, then ignore keypress
- mov ah,3 ;Get cursor position
- int 10h
- inc dl ;Increment column number
- cmp dl,cs:[columns] ;Increment row number if
- jna rt1 ; cursor wraps around
- xor dl,dl
- inc dh
- rt1:
- mov ah,2 ;Position cursor
- int 10h
- inc di ;Advance pointers
- inc cs:[bufferptr]
- rt2:
- ret
- move_right endp
- ;------------------------------------------------------------------------------
- ; CTRL_LEFT moves the cursor one word left.
- ;------------------------------------------------------------------------------
- ctrl_left proc near
- call move_left ;Move one character left
- cmp cs:[bufferptr],1 ;Beginning of line?
- je cl_exit ;Yes, then exit
- cmp byte ptr es:[di],32 ;Loop back if current char
- je ctrl_left ; is a space
- cmp byte ptr es:[di-1],32 ;Loop back if char to the
- jne ctrl_left ; left is not a space
- cl_exit:
- ret
- ctrl_left endp
- ;------------------------------------------------------------------------------
- ; CTRL_RIGHT moves the cursor one word right.
- ;------------------------------------------------------------------------------
- ctrl_right proc near
- call move_right ;Move one character right
- mov cl,[si] ;End-of-line?
- cmp cl,cs:[bufferptr] ;Yes, then exit
- jb cr_exit
- cmp byte ptr es:[di],32 ;Loop back if current char
- je ctrl_right ; is a space
- cmp byte ptr es:[di-1],32 ;Loop back if char to the
- jne ctrl_right ; left is not a space
- cr_exit:
- ret
- ctrl_right endp
- ;------------------------------------------------------------------------------
- ; HOME relocates the cursor to the beginning of the command line.
- ;------------------------------------------------------------------------------
- home proc near
- mov cl,cs:[bufferptr] ;Get position pointer
- dec cl ;Calculate distance from start
- xor ch,ch
- jcxz home_exit ;Exit if already there
- home1:
- push cx ;Save count
- call move_left ;Move left one space
- pop cx ;Retrieve count
- loop home1 ;Loop until done
- home_exit:
- ret
- home endp
- ;------------------------------------------------------------------------------
- ; EOL advances the cursor to the end of the command line.
- ;------------------------------------------------------------------------------
- eol proc near
- mov cl,[si] ;Get count
- cmp cl,cs:[bufferptr] ;Already at end?
- jb eol_exit ;Yes, then exit
- sub cl,cs:[bufferptr] ;Calculate distance from end
- inc cl
- xor ch,ch ;Byte to word in CX
- eol1:
- push cx ;Advance right CX times
- call move_right
- pop cx
- loop eol1
- eol_exit:
- ret
- eol endp
- ;------------------------------------------------------------------------------
- ; CLEAR_LINE clears the command line.
- ; Entry: DS:SI - Ptr to current line buffer
- ; BH - current video page
- ;------------------------------------------------------------------------------
- clear_line proc near
- mov cl,[si] ;Get count
- xor ch,ch
- jcxz cline2 ;Exit if no characters
- push cx ;Save count
- call home ;Home the cursor
- mov ah,3 ;Get cursor position
- int 10h
- pop cx ;Restore CX
- mov al,32 ;Print ASCII spaces
- cline1:
- call print_char
- loop cline1
- mov ah,2 ;Home cursor again
- int 10h
- mov byte ptr [si],0 ;Reset count
- cline2:
- ret
- clear_line endp
- ;----------------------------------------------------------------------------
- ; CMP CMDLINES - Compare the current cmd to one in stack
- ; Entry: ES:DI - Stacked command
- ; Exit: ZF - Set if compare passed
- ;----------------------------------------------------------------------------
- cmp_cmdlines proc near
- push di
- push si
- push ds
- lds si,dword ptr cmdstack_headl ;Get ptr to cmp string
- xor cx,cx
- lodsb
- or cl,al ;Get length of string
- jz cmp_cmdlines_2
- inc di
- call chk_buffend
- call chk_buffendsi
- cmd_cmdlines_1:
- cmp cs:chk_case,0 ;Flag determines if case
- jz cmd_cmdlines_11 ; respected.
- cmpsb
- jmp short cmd_cmdlines_12
- cmd_cmdlines_11:
- lodsb ;Ignore case check
- mov ah,es:[di]
- inc di
- or ax,2020h
- cmp al,ah
- cmd_cmdlines_12:
- pushf
- call chk_buffend
- call chk_buffendsi
- popf
- jne cmp_cmdlines_2
- loop cmd_cmdlines_1
- mov al,es:[di]
- cmp_cmdlines_2:
- pop ds
- pop si
- pop di
- ret
- cmp_cmdlines endp
- ;----------------------------------------------------------------------------
- ; SRCH_STACK searchs the command stack for a matching command.
- ; Exit: CF - clear if match found
- ; ES:DI - points to matching entry
- ;----------------------------------------------------------------------------
- srch_stack proc near
- assume cs:code,ds:nothing
- push di
- mov es,cs:[cmdstack_seg] ;Get ptr to head of stack
- mov di,cs:[cmdstack_curr]
- srch_stack_1:
- call get_prev ;Get ptr to prev command
- cmp di,cs:[cmdstack_head] ;See if at end of list
- je srch_stack_exit ;Yes, exit
- call cmp_cmdlines ;No, see if cmd matches
- jne srch_stack_1 ;No match, keep looking
- or al,al ;See if full command checked
- jne srch_stack_1
- clc
- pop cx ;Clear DI val on stack
- ret
- srch_stack_exit:
- stc
- pop di ;Restore original DI
- ret
- srch_stack endp
- ;----------------------------------------------------------------------------
- ; DEL_CMD Deletes an entry in the command stack list
- ; Entry: ES:DI - Ptr to entry to delete
- ; Exit: ES:DI - Ptr to last command in stack
- ;----------------------------------------------------------------------------
- del_cmd proc near
- assume cs:code,ds:nothing
- push si
- push ds
- push es
- pop ds
- mov si,di
- call get_next ;Get ptr to next command
- xchg si,di
- del_cmd_1:
- cmp di,cs:[cmdstack_head] ;See if at end of list
- je del_cmd_3 ;Yes, exit
- mov cl,ds:[si] ;Get length of cmd
- xor ch,ch
- inc cx ;Add 1 for count byte
- inc cx ;Add 1 for zero byte
- del_cmd_2:
- movsb ;Move next cmd over
- call chk_buffend ; current command.
- call chk_buffendsi
- loop del_cmd_2
- jmp short del_cmd_1
- del_cmd_3:
- mov cx,si ;Erase tail of last command.
- sub cx,di
- xor al,al
- push di
- del_cmd_4:
- stosb
- loop del_cmd_4
- pop di
- del_cmd_exit:
- pop ds
- pop si
- ret
- del_cmd endp
- ;----------------------------------------------------------------------------
- ; GET_PREV returns a pointer to the prev command in the stack.
- ; Entry: ES:DI - Ptr to current command
- ; Exit: ES:DI - Ptr to prev command
- ;----------------------------------------------------------------------------
- get_prev proc near
- assume cs:code,ds:nothing
- xor al,al ;Zero AL
- get_prev_1:
- dec di ;Skip past preceeding zero
- call chk_buffbase
- cmp di,cs:[cmdstack_head] ;See if at end of list
- je get_prev_3
- cmp es:[di],al ;If zero, keep scanning back
- jz get_prev_1 ; past erased command.
- get_prev_2:
- dec di ;Scan back to prev cmd
- call chk_buffbase
- cmp es:[di],al ;Chk for zero byte
- jnz get_prev_2
- inc di ;Scan forward to cmd
- call chk_buffend
- get_prev_3:
- ret
- get_prev endp
- ;----------------------------------------------------------------------------
- ; GET_NEXT returns a pointer to the next command in the stack.
- ; Entry: ES:DI - Ptr to current command
- ; Exit: ES:DI - Ptr to next command
- ;----------------------------------------------------------------------------
- get_next proc near
- assume cs:code,ds:nothing
- xor ax,ax ;Zero AL
- mov al,es:[di] ;Get cmd length
- add di,ax
- inc di ;Inc for cnt byte.
- call chk_buffend
- get_next_1:
- mov al,es:[di] ;Get next char
- cmp al,ah ;Ah == 0
- jne get_next_2
- cmp di,cs:[cmdstack_head] ;See if at end of list
- je get_next_2
- inc di
- call chk_buffend
- jmp short get_next_1
- get_next_2:
- ret
- get_next endp
- ;------------------------------------------------------------------------------
- ; CMD_RECORD records the latest command in the command stack.
- ; Entry: DS:SI - input buffer address
- ; CX - length of cmd to save
- ; Exit: ES:DI - Points to end of cmd stored
- ;------------------------------------------------------------------------------
- cmd_record proc near
- assume cs:code,ds:nothing
- inc cx ;Add 1 for zero byte
- les di,dword ptr cmdstack_headl ;Get head ptr
- cmd_record_1:
- movsb ;Store character
- call chk_buffend ;Inc cmd buff ptr
- loop cmd_record_1 ;Loop till done
- xor ax,ax
- stosb ;Store end of cmd byte
- push di
- cmd_record_2:
- call chk_buffend ;Inc cmd buff ptr
- cmp byte ptr es:[di],0 ;Continue until end of
- je cmd_record_3 ; next command
- stosb ;Store end of cmd byte
- jmp short cmd_record_2
- cmd_record_3:
- pop di
- cmd_record_exit:
- ret
- cmd_record endp
- ;------------------------------------------------------------------------------
- ; CHK_BUFFEND Checks the cmd buff ptr to see if it is valid
- ; Entry: ES:DI - Ptr to cmdstack buffer
- ; Exit: ES:DI - Updated
- ;------------------------------------------------------------------------------
- chk_buffend proc near
- assume cs:code,ds:nothing
- cmp di,cs:[cmdstack_end] ;See if at end of buff
- jae chk_buffend_1 ;Yes, reset ptr to base
- ret
- chk_buffend_1:
- sub di,cs:[cmdstack_size]
- ret
- chk_buffend endp
- ;------------------------------------------------------------------------------
- ; CHK_BUFFENDSI Checks the cmd buff ptr to see if it is valid
- ; Entry: SI - Ptr to cmdstack buffer
- ; Exit: SI - Updated
- ;------------------------------------------------------------------------------
- chk_buffendsi proc near
- assume cs:code,ds:nothing
- xchg si,di
- call chk_buffend
- xchg si,di
- ret
- chk_buffendsi endp
- ;------------------------------------------------------------------------------
- ; CHK_BUFFBASE Checks the cmd buff ptr to see if it is valid
- ; Entry: ES:DI - Ptr to cmdstack buffer
- ; Exit: ES:DI - Updated
- ;------------------------------------------------------------------------------
- chk_buffbase proc near
- assume cs:code,ds:nothing
- cmp di,cs:[cmdstack_base] ;See if at start of buff
- jbe chk_buffbase_1 ;Yes, reset ptr to base
- ret
- chk_buffbase_1:
- add di,cs:[cmdstack_size]
- ret
- chk_buffbase endp
- ;----------------------------------------------------------------------------
- ; WRITE_CMD1 outputs a command string
- ; Entry: ES:DI - string offset address
- ; DS:SI - current line buffer
- ; Exit: AL - character after string
- ;----------------------------------------------------------------------------
- write_command proc near
- assume cs:code,ds:nothing
- push di ;Save address
- call clear_line ;Clear input line
- pop di ;Retrieve string address
-
- push ds ;Save Ptr to line buffer
- push si
-
- push es ;Swap pointers
- push ds
- pop es
- pop ds
- xchg si,di
-
- xor cx,cx
- add cl,[si] ;Get string length
- movsb ;Store string length
- jcxz write2
- write1:
- lodsb
- call chk_buffendsi
- call print_char
- stosb ;Transfer character to buffer
- inc cs:[bufferptr] ;Advance pointer
- loop write1 ;Loop until done
- write2:
- pop si ;Restore line buff pointer
- pop ds
- ret
- write_command endp
- ;------------------------------------------------------------------------------
- ; NEW_LINE prints a carrage return and linefeed to the screen
- ;------------------------------------------------------------------------------
- new_line proc near
- mov al,13
- call print_char
- mov al,10
- call print_char
- ret
- new_line endp
- ;------------------------------------------------------------------------------
- ; PRINT_STRING writes an ASCII string to the command line.
- ; Entry: DS:SI - string address
- ; CX - number of characters
- ;------------------------------------------------------------------------------
- print_string proc near
- jcxz ps_exit ;Exit if no characters
- ps1:
- lodsb ;Get a byte
- call print_char ;Print a byte
- loop ps1 ;Loop until done
- ps_exit:
- ret
- print_string endp
- ;------------------------------------------------------------------------------
- ; PRINT_CHAR writes an ASCII character to the screen
- ; Entry: AL - character
- ;------------------------------------------------------------------------------
- print_char proc near
- push dx
- mov ah,2 ;Print the character
- mov dl,al ;Transfer it to DL
- int 21h ;Output character
- pop dx
- ret
- print_char endp
- ;------------------------------------------------------------------------------
- ; SET_CURSOR sets the cursor mode based on the state of the insert flag.
- ;------------------------------------------------------------------------------
- set_cursor proc near
- mov cx,cs:[points] ;Get scan lines/char
- mov ah,cs:[insert_flag] ;Test state of insert flag
- xor ah,cs:[insert_cursor]
- je setc1 ;Branch if not set
- xor ch,ch
- jmp short setc2
- setc1:
- mov ch,cl
- dec ch
- setc2:
- mov ah,1 ;Set cursor mode
- int 10h
- ret
- set_cursor endp
- ;-----------------------------------------------------------------------------
- ; HEX2ASC converts a binary number to ASCII and prints it to the screen.
- ; Entry: AX - binary number
- ;-----------------------------------------------------------------------------
- hex2asc proc near
- assume ds:nothing,es:nothing
- push bx
- push cx
- mov cx,5 ;Allow max of five digits
- hex_loop1:
- xor dx,dx ;Clear high word
- mov bx,10 ;Load number base
- div bx ;Divide by base (10)
- add dl,30h ;Convert to ascii
- push dx ;Save digit on stack
- loop hex_loop1
- mov cx,5 ;Allow max of five digits
- mov bl,"0" ;Set leading zero indicator
- hex_loop2:
- pop ax ;Get digit off stack
- or bl,al ;Don't print leading zeros.
- cmp bl,"0" ;The first non zero will
- je hex_1 ; change bl to non-zero.
- call print_char
- hex_1:
- loop hex_loop2
- hex_exit:
- pop cx
- pop bx
- ret
- hex2asc endp
- ;-----------------------------------------------------------------------------
- ; DELALIASENTRY - Deletes an alias entry
- ; Entry: ES:DI - pointer to the entry in the alias list to delete
- ; Exit: CF - clear if successful
- ;-----------------------------------------------------------------------------
- delete_aliasent proc near
- push cx ;Save registers
- push si
- push ds ;Yes, remove entry from list
-
- push es ; by moving the remainder of
- pop ds ; the list over this entry.
- mov si,ds:[di] ;Point SI to the next list
- add si,di ; entry.
- delent_1:
- cmp word ptr ds:[si],-1 ;Check for the end of the list
- je delent_2
- mov cx,ds:[si] ;Get size of entry
- rep movsb ;Copy next entry over current
- jmp short delent_1 ; entry.
- delent_2:
- mov word ptr es:[di],-1 ;Set end of list indicator
- pop ds ;Get back file buffer pointer
- pop si
- pop cx
- ret
- delete_aliasent endp
- ;============================================================================
- ; MUXINT processes calls to interrupt 2Fh
- ; Entry: AH - Device ID
- ; Exit: AL - 0FFh if AH = Alias device ID. Unchanged otherwise.
- ; ES - Code segment if AH = Alias device ID. Unchanged otherwise.
- ;============================================================================
- muxint proc far
- assume cs:code,ds:nothing,es:nothing
- cmp ax,1605h ;See if Windows launch
- je mux_winstart
- cmp ax,1606h ;See if Windows terminate
- je mux_winend
-
- cmp ax,4b05h ;See if switcher get instance
- je init_instance ; data.
-
- cmp ah,cs:[multiplex_id] ;Check for program ID
- je muxint_1 ;Its us, indicate installed.
- muxint_jmp:
- jmp cs:[int2Fh] ;Jump to old int
- mux_winend:
- test dl,01h ;See if enhanced mode Windows
- jne muxint_jmp
- dec cs:win_enhanced ;Clear Enhanced mode win flag
- jmp short muxint_jmp
- mux_winstart:
- test dl,01h ;See if enhanced mode Windows
- jne init_instance
- inc cs:win_enhanced
- init_instance:
- pushf
- call cs:[int2fh] ;Call old int
- mov word ptr cs:[sisNextDev],bx
- mov word ptr cs:[sisNextDev+2],es
- push cs ;ES:BX point to switcher struc
- pop es
- mov bx,offset StartupInfo
- iret
- muxint_1:
- mov al,-1 ;Indicate Alias installed
- push cs ;ES = installed code segment
- pop es
- iret
- muxint endp
-
- even ;Align stack on word boundry
- end_of_resident = $
-
- ;----------------------------------------------------------------------------
- ; Start of non-resident code.
- ;----------------------------------------------------------------------------
- final_install:
- rep movsb ;Copy alias list
- cld ;Correct DF if necessary
- mov di,aliaslist_size ;Init key assignment lists
- mov si,keylist_base
- mov cx,MAXKEYS
- mov keylist_base,di ;Copy key lists to area
- push cx ; just past alias buffer
- rep movsw
- pop cx
- mov cmdlist_base,di
- rep movsw
-
- xor al,al
- mov di,cmdstack_base ;Initialize command stack
- mov cx,cmdstack_size ; area with zeros
- jcxz tsr ;Branch if size is zero
- rep stosb
- tsr:
- mov ax,3100h ;Terminate and stay resident
- int 21h
- ;----------------------------------------------------------------------------
- ; Non-resident data.
- ;----------------------------------------------------------------------------
- alrdy_installed db 0 ;Installed flag
- other_seg dw 0 ;Segment of installed code
- databuff_seg dw 0 ;Segment of data buffer.
-
- alias_buffer dw 512 ;Extra buffer for alias list.
- aliaslist_end dw 0 ;Offset of end of the list.
- alias_inlist db 0 ;Flag used in alias list append
-
- infomsg1 db "PCMKEY uninstalled",0
- infomsg2 db 13,10,9,"Command stack size: ",0
- infomsg3 db 13,10,9,"Minimum stacked command length: ",0
- infomsg4 db 13,10,9,"Bytes free in alias buffer: ",0
- infomsg5 db 13,10,9,"Alias translation is ",0
- infomsg5d db "disabled",13,10,0
- infomsg5e db "enabled",13,10,0
- infomsg6 db 13,10,"//",9,"KEY ASSIGNMENTS",0
- infomsg7 db 13,10,"//",9,"ALIAS DEFINITIONS",0
- infomsg8 db 13,10,"For help type PCMKEY ?",0
-
- filemsg1 db 13,10,"Error in line ",0 ;File identification message.
- filemsg2 db " of file: "
- filenam_field db 78 dup (0) ;Name of current entry file.
-
- errmsg0 db "Need DOS 3.1 or greater",0
- errmsg1 db "PCMKEY not installed",0
-
- errmsg2 db 13,10,"Syntax: PCMKEY [alias [command]]"
- db "[/B n][/C][/D][/E][/F filename]",13,10
- db 14 dup (" ")
- db "[/I+|-][/K][/L][/M n][/Pc][/S n][/U]",13,10,10
- db 9,"PCMKEY alias command",13,10
- db 9,"PCMKEY [key] [function] or command",13,10,10
- db 9,"/B = Set buffer size*",13,10
- db 9,"/C = Toggle underline cursor for insert",13,10
- db 9,"/D = Disable alias translation",13,10
- db 9,"/E = Enable alias translation",13,10
- db 9,"/F = Define filename of command file",13,10
- db 9,"/I = Change ignore/match case in search",13,10
- db 9,"/K = List key assignments",13,10
- db 9,"/L = List aliases",13,10
- db 9,"/M = Minimum command length to stack",13,10
- db 9,"/P = Define command separator*",13,10
- db 9,"/S = Set size of command stack*",13,10
- db 9,"/U = Uninstall",13,10,10
- db 9,"* switches valid only at install time.",13,10
- db 0
-
- errmsg3 db "Can",39,"t uninstall",0
- errmsg4 db "Can",39,"t change parameter after installation",0
- errmsg5 db "Illegal number",0
- errmsg6 db "Can",39,"t find alias file",0
- errmsg8 db "Not enough memory",0
- errmsg9 db "Alias list full",0
- errmsg10 db "DOSKEY installed",0
- errmsg11 db "Invalid key assignment",0
- errmsg12 db "Number too big",0
- errmsg13 db "Alias not in list",0
- errmsg14 db "Error using Int 2Fh",0
- errmsg15 db "+ or - must follow /I",0
- errmsg16 db "Unsupported key combination",0
- errmsg17 db "Unknown editor command",0
- errmsg18 db "Bad $ switch",0
- errmsg19 db "Too many key assignments",0
-
- filebuf_size dw 0400h ;Size of input file buffer.
- max_list_size dw 1000h ;Max size of installed code.
-
- file_linecount dw 0 ;Line number being processed.
- caps_flag db 0
- param_found db 0 ;Cmd line parameter found flag
- append_cr db 0 ;Append cr to alias flag
-
- cmd_switches db "sfeldbumipkc*/" ;Letters of valid commands.
- cmd_switch_end = $
- cmd_jmp_tbl dw offset setstacksize ;This jump table is used to
- dw offset loadaliasfile ; call the routines that
- dw offset enablealias ; process the command line
- dw offset listalias1 ; arguments
- dw offset disablealias
- dw offset setlistbuffer
- dw offset remove
- dw offset minstacklen
- dw offset checkcase
- dw offset cmdsepchar
- dw offset listkeys
- dw offset inscursor
- dw offset comment_line ;Comments can be indicated by
- dw offset comment_line ; a /* or a //.
-
- keys dw 8047h,8048h,803dh,804bh,804dh
- dw 804fh,8050h,8052h,8053h,8473h
- dw 8474h,8475h,0008h,0009h,001bh
- dw 047fh,000dh,8041h,8043h,886eh
- dw 8871h,0403h,0407h,0408h,040dh
- keys_end = $
-
- keylist_entry dw offset home ;Jump table for standard
- dw offset prev_cmd ; keys. Groups of 5 match
- dw offset prev1_cmd ; keys table above.
- dw offset move_left
- dw offset move_right
-
- dw offset eol
- dw offset next_cmd
- dw offset toggle_ins
- dw offset delete
- dw offset ctrl_left
-
- dw offset ctrl_right
- dw offset ctrl_end
- dw offset backspace
- dw offset tab
- dw offset clr_cmd
-
- dw offset ctrl_bs
- dw offset enter
- dw offset dump_stack
- dw offset pick_stack
- dw offset clr_stack
-
- dw offset clr_aliases
- dw offset abort_cmd
- dw offset beep_cmd
- dw offset backspace ;Cmds duped in ctl chars
- dw offset enter ; for default action
-
- dw offset shift1_key ;Cmds not preassigned
- dw offset shift2_key
- dw offset shift3_key
- dw offset nop_cmd
- keylist_e_end = $
-
- keycmds db "home",0
- db "srchcmd",0
- db "prevcmd",0
- db "charleft",0
- db "charright",0
-
- db "end",0
- db "nextcmd",0
- db "toggleins",0
- db "del",0
- db "wordleft",0
-
- db "wordright",0
- db "del2eol",0
- db "bksp",0
- db "tab",0
- db "clrcmd",0
-
- db "wordbksp",0
- db "enter",0
- db "dumpstack",0
- db "pickcmd",0
- db "clrstack",0
-
- db "clraliases",0
- db "abortcmd",0
- db "beep",0
- db 1,0 ;Fake labels allow dual use
- db 1,0 ; of keylist for default
- ; key assignments.
- db "prefix1",0
- db "prefix2",0
- db "prefix3",0
- db "nop",0,0
-
- align 16
- keycodes dw 0027h,0322h,0 ,0 ; '
- dw 002ch,033ch,0 ,0 ; ,
- dw 002dh,035fh,0 ,8882h ; -
- dw 002eh,033eh,0 ,0 ; .
- dw 002fh,033fh,0 ,0 ; /
- dw 0030h,0329h,0 ,8881h ; 0
- dw 0031h,0321h,0 ,8878h ; 1
- dw 0032h,0340h,0 ,8879h ; 2
- dw 0033h,0323h,0 ,8880h ; 3
- dw 0034h,0324h,0 ,8881h ; 4
- dw 0035h,0325h,0 ,8882h ; 5
- dw 0036h,035eh,0 ,8883h ; 6
- dw 0037h,0326h,0 ,8884h ; 7
- dw 0038h,032ah,0 ,8885h ; 8
- dw 0039h,0328h,0 ,8886h ; 9
- dw 003bh,033ah,0 ,0 ; ;
- dw 003dh,032bh,0 ,8883h ; =
- dw 005bh,037bh,041bh,0 ; [
- dw 005ch,037ch,041ch,0 ; \
- dw 005dh,037dh,041dh,0 ; ]
- dw 0060h,037eh,0 ,0 ; `
-
- dw 0061h,0341h,0401h,881eh ; a
- dw 0062h,0342h,0402h,8830h ; b
- dw 0063h,0343h,0403h,882eh ; c
- dw 0064h,0344h,0404h,8820h ; d
- dw 0065h,0345h,0405h,8812h ; e
- dw 0066h,0346h,0406h,8821h ; f
- dw 0067h,0347h,0407h,8822h ; g
- dw 0068h,0348h,0408h,8823h ; h
- dw 0069h,0349h,0409h,8817h ; i
- dw 006ah,034ah,040ah,8824h ; j
- dw 006bh,034bh,040bh,8825h ; k
- dw 006ch,034ch,040ch,8826h ; l
- dw 006dh,034dh,040dh,8832h ; m
- dw 006eh,034eh,040eh,8831h ; n
- dw 006fh,034fh,040fh,8818h ; o
- dw 0070h,0350h,0410h,8819h ; p
- dw 0071h,0351h,0411h,8810h ; q
- dw 0072h,0352h,0412h,8813h ; r
- dw 0073h,0353h,0413h,881fh ; s
- dw 0074h,0354h,0414h,8814h ; t
- dw 0075h,0355h,0415h,8816h ; u
- dw 0076h,0356h,0416h,882fh ; v
- dw 0077h,0357h,0417h,8811h ; w
- dw 0078h,0358h,0418h,882dh ; x
- dw 0079h,0359h,0419h,8815h ; y
- dw 007ah,035ah,041ah,882ch ; z
- single_key_end = $
- dw 8047h,8347h,8477h,8897h ; home
- dw 8048h,8348h,0 ,8898h ; up
- dw 8049h,8349h,8484h,8899h ; pgup
- dw 804bh,834bh,8473h,889bh ; left
- dw 804dh,834dh,8474h,889dh ; right
- dw 804fh,834fh,8475h,889fh ; end
- dw 8050h,8350h,8450h,88a0h ; down
- dw 8051h,8351h,8476h,88a1h ; pgdn
- dw 8052h,8352h,0 ,88a2h ; ins
- dw 8053h,8353h,0 ,88a3h ; del
- dw 0008h,0308h,047fh,0 ; bksp
- dw 0009h,830fh,0 ,0 ; tab
- dw 000dh,030dh,040ah,0 ; enter
- dw 001bh,031bh,041bh,0 ; esc
- dw 0020h,0 ,0 ,8020h ; space
- dw 803bh,8354h,845eh,8868h ; F1
- dw 803ch,8355h,845fh,8869h ; F2
- dw 803dh,8356h,8460h,886ah ; F3
- dw 803eh,8357h,8461h,886bh ; F4
- dw 803fh,8358h,8462h,886ch ; F5
- dw 8040h,8359h,8463h,886dh ; F6
- dw 8041h,835ah,8464h,886eh ; F7
- dw 8042h,835bh,8465h,886fh ; F8
- dw 8043h,835ch,8466h,8870h ; F9
- dw 8044h,835dh,8467h,8871h ; F10
- keycodes_end = $
-
- keynames db "home",0
- db "up",0
- db "pgup",0
- db "left",0
- db "right",0
- db "end",0
- db "down",0
- db "pgdn",0
- db "ins",0
- db "del",0
- db "bksp",0
- db "tab",0
- db "enter",0
- db "esc",0
- db "space",0
- db "f1",0
- db "f2",0
- db "f3",0
- db "f4",0
- db "f5",0
- db "f6",0
- db "f7",0
- db "f8",0
- db "f9",0
- db "f10",0,0
- keynames_end = $
-
- keyletters db "',-./0123456789;=[\]`"
- db "abcdefghijklmnopqrstuvwxyz"
- keyletters_end = $
- ;----------------------------------------------------------------------------
- ; Initialization routine.
- ;----------------------------------------------------------------------------
- initialize proc near
- assume cs:code,ds:code,es:code
- cld
- mov ah,30h ;Get DOS version
- int 21h
- xchg al,ah ;Swap major, minor numbers
- mov dx,offset errmsg0 ;Bad DOS version
- cmp ax,30ah ;Run if DOS 3.1 or greater.
- jb jmp_disp_error
- mov dos_version,ax ;Save version number
-
- mov ax,4800h ;Check for DOSKEY
- int 2fh
- mov dx,offset errmsg10 ;DOSKEY installed
- or al,al
- jne jmp_disp_error
-
- mov bx,offset end_of_code + STACKSIZE ;Init ptrs
- mov sp,bx
- mov word ptr [aliaslist_ptr],bx
- mov ax,cs
- mov word ptr [aliaslist_ptr+2],ax
- mov word ptr [bx],-1 ;Initialize alias list
- lea cx,[bx+4] ; by writing a -1 as
- mov aliaslist_end,cx
- add bx,max_list_size
- mov aliaslist_size,bx
-
- mov di,bx ;Init key assignment lists
- mov si,offset keys
- mov cx,offset keys_end - offset keys
- shr cx,1
- mov keys_cnt,cx
- push cx
- rep movsw
- pop cx
- mov keylist_base,bx ;Init ptr to keylist
- add bx,MAXKEYS * 2
- mov di,bx
- mov si,offset keylist_entry
- rep movsw
- mov cmdlist_base,bx
- add bx,MAXKEYS * 2
-
- mov cl,4
- shr bx,cl
- mov ah,4ah ;Reduce memory allocation
- int 21h
-
- mov bx,filebuf_size ;Get size of file buffer,
- mov ah,48h ;Allocate memory block
- int 21h
- mov dx,offset errmsg8 ;Not enough memory msg
- jc jmp_disp_error
- mov databuff_seg,ax ;Save segment to file buffer.
-
- call find_installed
- jnc init1
- jmp_disp_error:
- jmp disp_error ; msg and exit.
- ;
- ;Copy the command line to the file buffer to treat as a one line file.
- ;
- init1:
- mov ax,databuff_seg ;Get segment of file buffer.
- mov es,ax ;Treat the command line as
- xor di,di ; a 1 line file.
- mov si,offset command_tail
- xor cx,cx
- or cl,[si] ;Get command line length
- je parse_line_end ;If zero, skip parse routine
- inc si ;Copy command line into file
- inc cx ; buffer.
- push cx
- rep movsb
- pop cx ;CX = file size.
- xor si,si ;Point SI to start of buffer
- push es
- pop ds ;Set DS to file buffer seg
- assume ds:nothing,es:nothing
- mov es,cs:[other_seg] ;Set ES to installed code
- ;
- ;Parse command line and command files.
- ;
- parse_line_loop:
- xor bl,bl
- call scanline ;Get 1st character
- jc parse_2 ;If carriage return, skip line
- cmp al,"/" ;Compare character to switch.
- je parse_switch_found
- cmp al,"?" ;See if help character
- mov dx,offset errmsg2 ;Command not found msg
- je disp_error
- call setkey ;Must be alias definition
- jc disp_error
- mov param_found,1 ;Set parameter found flag
- jmp short parse_2 ;Return to parse loop
- parse_switch_found:
- mov param_found,1 ;Set parameter found flag
- lodsb ;Get command line switch
- dec cx
- cmp al,'A' ;Convert to lower case if
- jb parse_1 ; necessary.
- cmp al,'Z'
- ja parse_1
- or al,20h
- parse_1:
- push cx ;Scan the list of allowable
- push es ; command switches. If switch
- push cs ; found, use its position for
- pop es ; an index into the list of
- mov di,offset cmd_switches ; routines.
- mov cx,offset cmd_switch_end - offset cmd_switches
- mov bx,offset cmd_switch_end - offset cmd_switches - 1
- repne scasb
- mov ax,cx ;Copy index into list
- pop es
- pop cx
- mov dx,offset errmsg2 ;Command not found msg
- jne disp_error
- sub bx,ax ;Compute offset into list
- shl bx,1 ;Convert to word offset
- call cs:[bx+offset cmd_jmp_tbl] ;Call command routine.
- jc disp_error ;If error terminate parse.
- parse_2:
- jcxz parse_line_end ;If at file end, exit parse.
- jmp short parse_line_loop
- ;
- ;See if installed. If not, install.
- ;
- parse_line_end:
- cmp cs:[param_found],1 ;See if any parameters found
- je init2 ;If already installed and
- cmp cs:[alrdy_installed],0 ; no parameters on the
- je init2 ; command line, default to
- mov es,cs:[other_seg] ; showing program information
- call listalias
- init2:
- mov ah,49h ;Release memory block used
- mov es,cs:[databuff_seg] ; for file buffer.
- int 21h
- push cs
- pop ds
- assume ds:code
- mov word ptr databuff_seg,0 ;Indicate file buff released
- cmp alrdy_installed,0 ;If not already installed,
- je install ; jump to install routine.
- exit:
- mov ax,4C00h ;Terminate with RC = 0
- int 21h
- ;
- ;Display error message.
- ;
- assume ds:nothing
- disp_error:
- xor ax,ax ;If file buffer still
- or ax,cs:databuff_seg ; allocated, deallocate it.
- jz disp_error0
- mov ah,49h ;Release memory block used
- mov es,ax ; for file buffer.
- int 21h
- disp_error0:
- push cs
- pop ds
- assume ds:code
- cmp byte ptr filenam_field,0
- je disp_error1 ;If processing a file, print
- push dx ; a message informing the
- mov dx,offset filemsg1 ; user the filename being
- call printmsg ; processed and the line
- mov ax,file_linecount ; that the error occured.
- call hex2asc
- mov dx,offset filemsg2
- call printmsgcr
- pop dx
- disp_error1:
- call printmsgcr ;print string
- mov ax,4c01h ;Terminate with RC = 1
- int 21h
- ;
- ;Install routine. Find segment of COMMAND.COM, hook into int 21h, 2Fh and TSR.
- ;
- install:
- mov dx,offset program ;Display copyright message
- call printmsg
- ;
- ;Set up pointers to the cmd stack and to move the alias list to the end of the
- ;command stack so it takes up less space when ALIAS resident.
- ;
-
- mov di,RES_STACK ;Get base of internal stack
- mov work_buff_ptr,di ;Copy ptr to alias buffer
- add di,128 ;Add size of buffer
- mov cmdstack_base,di ;Copy for start of cmd stack
- mov cmdstack_head,di
- mov cmdstack_curr,di
-
- mov cmdstack_seg,ds
- add di,cmdstack_size
- mov cmdstack_end,di
-
- mov si,word ptr aliaslist_ptr ;Save start of the
- mov cx,aliaslist_end ; alias list.
- mov word ptr aliaslist_ptr,di ;Save new pointer.
- sub cx,si ;Compute size of list.
- mov dx,di ;See if we have enough room
- add dx,cx ; for everything in one seg.
- add dx,alias_buffer ;Add additional space for list
- mov aliaslist_size,dx ;Save pointer to end of seg
- add dx,MAXKEYS * 4 ;Add room for key lists
-
- mov ax,offset command_tail
- mov word ptr [temp_buff],ax
- mov word ptr [temp_buff+2],cs
- ;
- ;Init switcher structures
- ;
- mov word ptr [TempBlockPtr+2],cs
- mov word ptr [TempBlockPtr],ax
-
- mov word ptr [DataBlockPtr+2],cs
- mov word ptr [DataBlockPtr],offset DataBlock
- mov word ptr [DataBlockSize],INSTDATASIZE
-
- mov word ptr [StackBlockPtr+2],cs
- mov word ptr [StackBlockPtr],offset end_of_resident
- mov bx,dx
- sub bx,offset end_of_resident ;Compute size of
- mov word ptr [StackBlockSize],bx ; Data save area
-
- mov word ptr [sisInstData+2],cs
- mov word ptr [sisInstData],offset DataBlockPtr
-
- push dx
- mov ax,1600h ;See if Enhanced mode windows
- int 2fh
- or al,al
- je nowin
- inc win_enhanced ;Set enhanced mode flag
- nowin:
- ;
- ;Revector interrupts 21h and 2Fh (if necessary).
- ;
- mov ax,3521h ;Get interrupt 21 (DOS)
- int 21h ; vector.
- mov word ptr [int21h],bx
- mov word ptr [int21h+2],es
- push dx ;Save memory size parameter
- mov ax,2521h ;Point int 21 to internal
- mov dx,offset dosint ; routine.
- int 21h
-
- mov ax,352fh ;Get interrupt 2F (MUX)
- int 21h ; vector.
- mov word ptr [int2fh],bx
- mov word ptr [int2fh+2],es
- mov ax,252fh ;Point int 2F to internal
- mov dx,offset muxint ; routine.
- int 21h
-
- pop dx ;Get Ptr to end of resident
- add dx,15 ;Convert memory needed to
- shr dx,1 ; paragraphs.
- shr dx,1
- shr dx,1
- shr dx,1
- cmp di,si ;Check for overlap in the move
- jb install_2 ;If overlap, copy list from
- std ; the top down to avoid
- add di,cx ; overwriting the list.
- add si,cx
- dec si
- dec di
- install_2:
- push ds ;ES = DS
- pop es
- jmp final_install ;Jump to safe place for move.
- initialize endp
-
- ;-----------------------------------------------------------------------------
- ; CMPHEADER compares the first 16 bytes of this file with the segment
- ; pointed to by ES.
- ; Entry: DS - code segment
- ; ES - pointer to segment to compare
- ; Exit: ZF - 0 = segments match.
- ;-----------------------------------------------------------------------------
- cmpheader proc near
- mov si,offset main+2 ;Search this segment for ASCII
- mov di,si ; fingerprint.
- mov cx,16
- repe cmpsb
- ret
- cmpheader endp
- ;-----------------------------------------------------------------------------
- ; FIND INSTALLED Find the installed code by scanning the memory control blocks.
- ; Exit: AX - Segment of installed code if found.
- ; CF - Clear if installed code found
- ;-----------------------------------------------------------------------------
- find_installed proc near
- assume ds:code,es:code
- mov cx,16 ;Try 16 different IDs.
- find_installed_1:
- xor ax,ax
- mov es,ax
- mov ah,multiplex_id ;Load ID. Use Int 2Fh to
- int 2fh ; reach installed code so
- or al,al ; that we are compatible
- jne find_installed_2 ; with 386 memory managers.
- push cs
- pop es ;If AL not changed, ALIAS not
- jmp short find_installed_4 ; installed.
- find_installed_2:
- push cx
- call cmpheader ;See if really Alias by
- pop cx ; comparing file headers.
- je find_installed_3
- inc multiplex_id ;ID used by another program.
- loop find_installed_1 ; Change and try again.
- push cs
- pop es
- mov dx,offset errmsg14 ;All IDs taken, print error
- jmp find_installed_exit
- find_installed_3:
- inc alrdy_installed ;Set installed flag
- find_installed_4:
- clc
- find_installed_exit:
- mov other_seg,es ;Save seg of installed code
- ret
- find_installed endp
-
- ;-----------------------------------------------------------------------------
- ; PRINTMSG prints the message pointed to by DX to the screen.
- ; Entry: DX - pointer to ASCII message terminated by 0
- ;-----------------------------------------------------------------------------
- printmsg proc near
- assume ds:nothing,es:nothing
- push si
- push ds
- push cs
- pop ds
- assume ds:code
- mov si,dx
- printmsg1:
- lodsb
- or al,al
- je printmsg2
- call print_char
- jmp short printmsg1
- printmsg2:
- pop ds
- pop si
- ret
- printmsg endp
-
- ;-----------------------------------------------------------------------------
- ; PRINTMSGCR calls PRINTMSG, then appends a carriage return to the message.
- ; Entry: DX - pointer to ASCII message terminated by $
- ;-----------------------------------------------------------------------------
- printmsgcr proc near
- assume ds:nothing,es:nothing
- push dx
- call printmsg
- mov dx,offset endmsg
- call printmsg
- pop dx
- ret
- printmsgcr endp
-
- ;-----------------------------------------------------------------------------
- ; SETSTACKSIZE - Sets the size of the command line stack.
- ; Entry: DS:SI - points to stack size in ascii
- ; Exit: CF - Clear if sucessful, Set if error, DX points to error msg.
- ;-----------------------------------------------------------------------------
- setstacksize proc near
- assume ds:nothing,es:nothing
- xor bl,bl ;Check for installed code
- call setparameter ;Get num and convert to binary
- jc setstack_exit ;Check for error
- mov dx,20h
- mul dx
- je setstack_1
- cmp ax,128
- ja setstack_1 ;Stack must be at least 1
- mov ax,128 ; max cmd length in size.
- setstack_1:
- mov cs:[cmdstack_size],ax ;Save parameter
- setstack_exit:
- ret
- setstacksize endp
-
- ;-----------------------------------------------------------------------------
- ; SETLISTBUFFER - Sets the size of the additional buffer reserved for alias
- ; list expansion.
- ; Entry: DS:SI - points to buffer size in ascii
- ; Exit: CF - Clear if sucessful, Set if error, DX points to error msg.
- ;-----------------------------------------------------------------------------
- setlistbuffer proc near
- assume ds:nothing,es:nothing
- xor bl,bl ;Check for installed code
- call setparameter ;Get num and convert to binary
- jc setlistbuffer_exit ;Check for error
- mov cs:[alias_buffer],ax ;Save buffer size parameter
- setlistbuffer_exit:
- ret
- setlistbuffer endp
-
- ;-----------------------------------------------------------------------------
- ; MINSTACKLEN - sets the minimum length of a command to stack.
- ; Entry: ES - segment of the installed code
- ; DS:SI - points to buffer size in ascii
- ; Exit: CF - Clear if sucessful, Set if error, DX points to error msg.
- ;-----------------------------------------------------------------------------
- minstacklen proc near
- assume ds:nothing,es:nothing
- mov bl,1 ;Don't check for installed code
- call asc2bin ;Get num and convert to binary
- jc minstacklen_exit ;Check for error
- cmp al,126
- jb minstacklen_1
- mov dx,offset errmsg12 ;Stack length too big
- stc
- jmp short minstacklen_exit
- minstacklen_1:
- or al,al ;Make sure min length is not
- jne minstacklen_2 ; specified at 0. If so,
- inc al ; change to 1.
- minstacklen_2:
- mov es:[minlength],al ;Save minimum length parameter
- minstacklen_exit:
- ret
- minstacklen endp
-
- ;-----------------------------------------------------------------------------
- ; SETPARAMETER - Common code used by the set stack and set buffer and set
- ; minimum command length routines.
- ; Entry: DS:SI - points to ascii number
- ; BL - Flag to indicate check for installed code, BL=0, check.
- ; Exit: CF - Clear if sucessful, Set if error.
- ;-----------------------------------------------------------------------------
- setparameter proc near
- assume ds:nothing,es:nothing
- mov dx,offset errmsg4 ;Can't change parameter msg
- cmp cs:[alrdy_installed],1 ;If already installed don't
- je setparam_error ; change parameter.
- call asc2bin
- setparam_exit:
- ret
- setparam_error:
- stc ;Set error flag.
- jmp short setparam_exit
- setparameter endp
-
- ;-----------------------------------------------------------------------------
- ; CHECKCASE - sets the respect case flag for command stack searches.
- ; Entry: ES - segment of the installed code
- ; DS:SI - points to check case switch
- ; Exit: CF - Clear if sucessful, Set if error, DX points to error msg.
- ;-----------------------------------------------------------------------------
- checkcase proc near
- assume ds:nothing,es:nothing
- lodsb ;Get cmd line switch
- dec cx
- xor ah,ah ;Assume no check case
- cmp al,'-'
- je checkcase_1
- inc ah
- cmp al,'+'
- jne checkcase_error ;If not + or -, error.
- checkcase_1:
- mov es:chk_case,ah
- clc
- checkcase_exit:
- ret
- checkcase_error:
- stc
- mov dx,offset errmsg15
- jmp short checkcase_exit
- checkcase endp
- ;-----------------------------------------------------------------------------
- ; CMDSEPCHAR - sets the multiple command seperator character
- ; Entry: ES - segment of the installed code
- ; DS:SI - points to sep char
- ; Exit: CF - Clear if sucessful, Set if error, DX points to error msg.
- ;-----------------------------------------------------------------------------
- cmdsepchar proc near
- assume ds:nothing,es:nothing
- mov dx,offset errmsg4 ;Can't change parameter msg
- cmp cs:[alrdy_installed],1 ;If already installed don't
- stc ; change parameter.
- je cmdsepchar_exit
- lodsb ;Get cmd line switch
- dec cx
- mov es:multi_switch,al
- clc
- cmdsepchar_exit:
- ret
- cmdsepchar endp
-
- ;-----------------------------------------------------------------------------
- ; SRCH_LIST determines if a string is in a list.
- ; Entry: DS:SI - Pointer to *end* ASCII string to find.
- ; CS:DI - Pointer to list of ASCIIZ strings.
- ; DX - Length of string to search for.
- ; Exit: CF - Clear if string found
- ; BX - If CF clear, index into list
- ;-----------------------------------------------------------------------------
- srch_list proc near
- assume cs:code,ds:nothing,es:nothing
- push cx
- push si
- push es
-
- push cs
- pop es
- xor bx,bx ;Zero index counter
- jcxz srchl_3
- sub si,dx
- dec si
- srchl_1:
- push si
- mov cx,dx ;Restore command size
- repe cmpsb ;Compare command
- pop si
- jne srchl_11
- cmp byte ptr es:[di],0 ;See if at end of compare str
- je srch_list_exit
- srchl_11:
- inc bx ;Inc count in list
- xor al,al
- cmp es:[di-1],al ;See if at end of word
- jne srchl_2
- dec di
- srchl_2:
- mov cx,10 ;Scan to next zero
- repne scasb
- cmp es:[di],al ;See if second zero. If so
- jne srchl_1 ; end of list.
- srchl_3:
- stc ;Indicate string not found
- srch_list_exit:
- pop es
- pop si
- pop cx
- ret
- srch_list endp
-
- ;-----------------------------------------------------------------------------
- ; LCASE_STR - Converts a string enclosed in {} to lower case.
- ; Entry: DS:SI - Pointer to string
- ; CX - Max length of string
- ; Exit: DX - Length of string
- ;-----------------------------------------------------------------------------
- lcase_str proc near
- xor dx,dx ;Zero length count
- lcase_1:
- lodsb
- cmp al,"]"
- je lcase_exit
- cmp al,"A"
- jb lcase_2
- cmp al,"Z"
- ja lcase_2
- or al,20h ;Convert to lower case
- lcase_2:
- inc dx
- loop lcase_1
- stc ;Error because eol
- ret
- lcase_exit:
- dec cx ;Carry not changed by dec
- ret
- lcase_str endp
-
- ;-----------------------------------------------------------------------------
- ; LISTKEYS prints the keys assignments.
- ; Entry: ES - segment of the installed code
- ;-----------------------------------------------------------------------------
- shifts db "ssca321"
- shifts_end = $
- listkeys proc near
- assume ds:nothing,es:nothing
- push cx
- push si
- push ds
- push es
- mov ax,es ;DS = installed seg
- mov ds,ax
- push cs ;ES = CS
- pop es
-
- assume es:code
-
- mov dx,offset infomsg6 ;Print header
- call printmsgcr
-
- mov si,ds:keylist_base
- mov bx,ds:cmdlist_base
- mov cx,ds:keys_cnt
- listkey_1:
- push cx
- call printtab
- mov al,"[" ;Print opening bracket
- call print_char
- lodsw
- push ax
- mov cx,offset shifts_end - offset shifts
- mov di,offset shifts
- listkey_1a:
- shr ah,1
- jc listkey_1b
- inc di
- loop listkey_1a
- jmp short listkey_12
- listkey_1b:
- mov al,cs:[di]
- call print_char
- mov al,'-'
- call print_char
- listkey_12:
- pop ax
- and ah,8fh ;Strip off custom shifts
- mov di,offset keycodes
- mov cx,(offset keycodes_end - offset keycodes) shr 1
- repne scasw
- jne listkey_7
- dec di
- dec di
- cmp di,offset single_key_end
- jae listkey_2 ;See if single char or
- and di,0fff8h ; named key.
- mov ax,es:[di]
- call print_char
- jmp short listkey_5
- listkey_1j:
- jmp short listkey_1
- listkey_2:
- sub di,offset single_key_end
- mov cl,3
- shr di,cl
- mov cx,di
- mov di,offset keynames
- call getname
- call printmsg
- listkey_5:
- mov al,"]" ;Print closing bracket
- call print_char
- call printtab
- call printtab
- mov ax,ds:[bx] ;Get command function ptr
-
- cmp ax,offset alias_str ;See if text assignment
- je listkey_8
-
- mov di,offset keylist_entry
- mov cx,(offset keylist_e_end - offset keylist_entry) shr 1
- repne scasw
- jne listkey_7
- sub di,offset keylist_entry
- shr di,1
- mov cx,di
- dec cx
- mov di,offset keycmds ;Find command name and
- call printname ; print it.
- listkey_7:
- mov dx,offset endmsg
- call printmsg
- inc bx ;Advance cmd tbl ptr
- inc bx
- pop cx
- loop listkey_1j
- clc
- pop es
- pop ds
- pop si
- pop cx
- ret
- listkey_8:
- mov ax,ds:[si-2] ;Get back key
- push es
- push ds
- pop es
- call searchkey ;Find text
- pop es
- push si
- lea si,[di+6]
- xor cx,cx
- mov cl,[di+3]
- listkey_9:
- lodsb ;Print it
- call print_char
- loop listkey_9
- listkey_10:
- pop si
- jmp short listkey_7
- listkeys endp
- ;-----------------------------------------------------------------------------
- ; PRINTNAME prints a string from a list
- ; Entry: CS:DI - pointer to list
- ; CX - entry to return in list
- ;-----------------------------------------------------------------------------
- printname proc near
- assume ds:nothing,es:nothing
- mov al,"["
- call print_char
- call getname
- call printmsg ;Print it
- mov al,"]"
- call print_char
- ret
- printname endp
- ;-----------------------------------------------------------------------------
- ; GETNAME returns a pointer to a string in a list
- ; Entry: CS:DI - pointer to list
- ; CX - entry to return in list
- ; Exit: CS:DX - ptr to string
- ;-----------------------------------------------------------------------------
- getname proc near
- assume ds:nothing,es:nothing
- push es
- push cs
- pop es
- jcxz getname_exit ;If no length, punt
- xor al,al
- getname_1:
- cmp cs:[di],al ;See if at end of list
- je getname_exit
- push cx
- mov cx,128
- repne scasb
- pop cx
- loop getname_1
- getname_exit:
- mov dx,di
- pop es
- ret
- getname endp
- ;-----------------------------------------------------------------------------
- ; SETKEY modifies the alias list to add function key definitions.
- ; Entry: DS:SI - pointer to string identifing the function key
- ; ES - pointer to segment of installed code
- ; Exit: CF - clear if successful
- ;-----------------------------------------------------------------------------
- setkey proc near
- assume ds:nothing,es:nothing
- push bp
- mov bp,sp
- sub sp,2
-
- cmp al,"[" ;Determine alias or key
- je setkey_1
- dec si ;Backup before last key
- inc cx
- jmp setkey_12
- setkey_1:
- lodsb ;Get shift character
- dec cx
- jz setkey_3 ;Make sure other char
- xor bx,bx
- cmp byte ptr [si],"-" ;See if shift modifier
- jne setkey_4
- or al,20h ;Convert to lc
- add bl,2 ;Assume Shift shift
- cmp al,"s"
- je setkey_2
- add bl,2 ;Assume Ctl shift
- cmp al,"c"
- je setkey_2
- add bl,2 ;Assume Alt shift
- cmp al,"a"
- je setkey_2
- mov bx,4000h
- cmp al,"1" ;First optional shift
- je setkey_2
- mov bh,20h
- cmp al,"2" ;Second optional shift
- je setkey_2
- mov bh,10h
- cmp al,"3" ;Third optional shift
- jne setkey_badkey
- setkey_2:
- inc si ;Skip past '-'
- lodsb ;Get next char
- sub cx,2
- setkey_3:
- jbe setkey_badkey
- setkey_4:
- mov [bp-2],bx ;Save shift param
- ;
- ; Look up keycode in key name table
- ;
- push ax
- dec si ;Back up to first char
- inc cx ; in keyname
- call lcase_str ;convert string to lc
- pop ax
- jc setkey_badkey
- cmp dx,1 ;See if string length 1
- jne setkey_5
- push cx
- mov di,offset keyletters
- mov cx,offset keyletters_end - offset keyletters
- push es
- push cs
- pop es
- repne scasb
- pop es
- pushf
- not cx
- add cx,offset keyletters_end - offset keyletters
- mov bx,cx ;Copy key table index
- popf
- pop cx
- je setkey_6
- xor ax,ax
- jmp short setkey_61
- setkey_5:
- mov di,offset keynames ;Search list for name
- call srch_list
- jc setkey_badkey
- add bx,offset keyletters_end - offset keyletters
- setkey_6:
- shl bx,1 ;mul by entry size
- shl bx,1
- shl bx,1
- add bl,[bp-2] ;Add shift offset
- adc bh,0
- mov ax,cs:[bx+offset keycodes]
- setkey_61:
- mov dx,offset errmsg16 ;Unsupported key msg
- or ax,ax
- jz setkey_error
- or ah,[bp-1] ;OR shift flags
- jmp short setkey_7
- setkey_badkey:
- mov dx,offset errmsg11 ;Bad key assignment msg
- setkey_error:
- stc
- jmp setkey_exit1
- setkey_exitj:
- jmp setkey_exit
- setkey_7:
- mov [bp-2],ax ;Save key
- lodsb ;Get next character
- dec cx
- jz setkey_8
- cmp al," "
- jbe setkey_8 ;Check for another char
-
- cmp al,"*" ;Check to see if an * is
- jne setkey_badkey ; appended to indicate
- mov cs:[append_cr],1 ; append cr to command.
- ;
- ; See if key currently in list
- ;
- setkey_8:
- push cx ;Check current keylist for
- mov di,es:keylist_base ; for key being assigned.
- mov cx,es:keys_cnt
- mov ax,[bp-2] ;Get key combination
- repne scasw
- mov ax,cx
- pop cx
- jne setkey_9
- mov bx,di
- sub bx,es:keylist_base
- call del_entry ;Key found. Delete entry
- mov di,es:cmdlist_base ; in both key list and
- add di,bx ; cmd list.
- cmp word ptr es:[di-2],offset alias_str
- pushf
- call del_entry
- dec es:keys_cnt
- popf ;See if key cmd an alias
- jne setkey_9
- mov ax,[bp-2] ;Get key combination
- call searchkey ;Search alias list
- jc setkey_9
- push si
- push ds
- push es
- pop ds ;DS:SI = entry to delete
- mov si,di
- call delete_aliasent
- pop ds
- pop si
- setkey_9:
- jcxz setkey_exitj
- xor bl,bl ;Point to next word
- call scanline ;See if cmd assignment or
- jc setkey_exit ; alias.
- mov dx,offset alias_str
- cmp al,"["
- jne setkey_10
-
- call lcase_str ;convert string to lc
- jc setkey_badkey
- mov di,offset keycmds ;Search list for cmd name
- call srch_list
- mov dx,offset errmsg17 ;Unknown editor cmd
- jc setkey_exit1
- shl bx,1 ;mul by entry size
- mov dx,cs:[bx+offset keylist_entry]
- setkey_10:
- mov di,es:keylist_base ;Save key code in
- mov ax,es:keys_cnt ; key list
- cmp ax,MAXKEYS
- jb setkey_11
- mov dx,offset errmsg19 ;Too many keys
- jmp setkey_error
- setkey_11:
- shl ax,1
- add di,ax
- mov bx,[bp-2] ;Save key code
- mov es:[di],bx
- inc es:keys_cnt
-
- mov di,es:cmdlist_base ;Save key cmd in cmd list.
- add di,ax
- mov es:[di],dx
- cmp dx,offset alias_str
- jne setkey_exit
- sub si,4 ;Back up to keycode.
- add cx,4
- mov word ptr ds:[si],5050h ;Save fake key on cmd line
- setkey_12:
- call setalias ;Use SETALIAS to save text
- jnc setkey_13
- dec es:keys_cnt ;If error, remove key
- jmp short setkey_exit1
- setkey_13:
- mov ax,5050h
- call searchkey
- mov bx,[bp-2] ;Save real key code
- mov es:[di+4],bx
- mov byte ptr es:[di+2],0 ;Indicate key not alias.
- setkey_exit:
- clc
- setkey_exit1:
- mov sp,bp
- pop bp
- ret
- setkey endp
- ;-----------------------------------------------------------------------------
- ; DEL_ENTRY - Deletes an entry in a word sized list
- ; Entry: ES:DI - Points to entry to delete + 1
- ; AX - Number of entries remaining in list
- ;-----------------------------------------------------------------------------
- del_entry proc near
- assume ds:nothing,es:nothing
- push cx
- mov cx,ax
- jcxz del_entry_exit
- del_entry_1:
- mov dx,es:[di]
- mov es:[di-2],dx
- inc di
- inc di
- loop del_entry_1
- del_entry_exit:
- pop cx
- ret
- del_entry endp
- ;-----------------------------------------------------------------------------
- ; SETALIAS modifies the alias list according to command line agruments.
- ; Entry: DS:SI - pointer to string to be inserted into alias list.
- ; ES - pointer to segment of installed code.
- ; Exit: CF - clear if successful
- ;-----------------------------------------------------------------------------
- setalias proc near
- assume ds:nothing,es:nothing
- push bp
- push es
- xor bl,bl ;Find 1st character on
- call scanline ; command line.
- jnc setalias_1 ;If at end of line, exit
- jmp setalias_exit1 ; routine.
- ;
- ;Get length of alias, then search list for matching alias
- ;
- setalias_1:
- dec si ;Backup to before 1st char.
- inc cx
- call searchalias ;Is there already an alias?
- mov byte ptr cs:[alias_inlist],0 ;Assume not in list
- jc setalias_2 ;No, continue.
- inc byte ptr cs:[alias_inlist]
- call delete_aliasent ;Delete entry from list
- setalias_2:
- ;
- ;Append new alias to the end of the list.
- ;
- mov bp,di ;Save ptr to end of list.
- add di,4 ;Move past length fields.
- push es ;Get max size of alias list.
- mov es,cs:[other_seg]
- mov dx,es:[aliaslist_size]
- pop es
- ;
- ;Append alias to list.
- ;
- xor ax,ax ;Clear character counter
- setalias_3:
- lodsb ;Get byte
- dec cx ;Decriment buffer counter.
- jcxz setalias_4 ;If at end of file, exit.
- cmp al,13 ;See if at end of line.
- jne setalias_6 ;No, continue.
- setalias_4:
- cmp byte ptr cs:[alias_inlist],0
- jne setalias_5 ;Was alias in list?
- jmp setalias_notnfil ;No, incomplete alias specifed
- setalias_5:
- jmp setalias_exit ;Yes, alias simply erased.
- setalias_6:
- cmp al,' ' ;See if at end of tag.
- je setalias_8 ;Yes, exit copy loop
- cmp al,9 ;Check for tab
- je setalias_8
- cmp di,dx ;See if alias list is full
- jbe setalias_7 ;No, continue
- jmp setalias_full ;Yes, exit routine
- setalias_7:
- stosb ;No, add character to list
- inc ah ;Inc size of tag
- jmp short setalias_3
- setalias_8:
- mov es:[bp+2],ah ;Save size of alias
- ;
- ;Append command to alias list.
- ;
- mov cs:[caps_flag],0 ;Initialize setcaps flag.
- xor bx,bx ;Find 1st character in
- call scanline ; command.
- jc setalias_5 ;If no command, exit
- xor ah,ah ;Clear character counter
- setalias_9:
- cmp al,"%" ;Check for environment var
- jne setalias_11 ; by checking for % signs.
- cmp cs:[caps_flag],0 ;If caps flag set capitialize
- jne setalias_10 ; string before saving.
- mov bl,ds:[si] ;Get next character
- cmp bl,'*'
- je setalias_11
- cmp bl,"0" ;If numeric, assume this is
- jb setalias_10 ; a line parameter, not an
- cmp bl,"9" ; environment variable so
- jbe setalias_11 ; don't set caps flag.
- cmp bl,"%" ;Don't let double % signs
- je setalias_11 ; indicate environment var.
- setalias_10:
- not byte ptr cs:[caps_flag] ;Toggle caps flag
- setalias_11:
- cmp cs:[caps_flag],0 ;Capitialize environment
- je setalias_12 ; variables so they will
- call capit ; match when searched for in
- ; the environment block.
- setalias_12:
- cmp al,'$' ;Check for DOSKEY sequence
- jne setalias_129 ;If $0-9 or $*, just sub
- mov bl,ds:[si] ; % for $.
- cmp bl,'*'
- je setalias_121
- cmp bl,'0'
- jb setalias_122
- cmp bl,'9'
- ja setalias_122
- setalias_121:
- mov al,'%'
- jmp short setalias_129
- setalias_j9:
- jmp short setalias_9
- setalias_122:
- lodsb ;Get next char
- dec cx
- call capit
- cmp al,'$'
- je setalias_129
- mov cs:[caps_flag],0 ;Clear cap flag
- mov bl,al ;Check for b, g, l, t or $.
- mov al,'<'
- cmp bl,'L'
- je setalias_129
- mov al,'|'
- cmp bl,'B'
- je setalias_129
- mov al,'>'
- cmp bl,'G'
- je setalias_129
- mov al,es:[multi_switch]
- cmp bl,'T'
- je setalias_129
- mov dx,offset errmsg18 ;Bad $ switch
- jmp short setalias_error
- setalias_129:
- cmp di,dx ;See if alias list is full
- ja setalias_full ;Yes, exit routine
- stosb ;Append character on list
- inc ah ;Inc character counter.
- jcxz setalias_13 ;Check for end of file.
- lodsb ;Get next character
- dec cx ;Dec file counter.
- cmp al,13 ;See if carriage return.
- jne setalias_j9 ;If not continue
- setalias_13:
- cmp cs:[append_cr],1 ;If flag set, append carrage
- jne setalias_14 ; return to command.
- mov al,13
- inc ah
- stosb
- mov cs:[append_cr],0 ;Clear flag
- setalias_14:
- mov es:[bp+3],ah ;Save command size
- mov word ptr es:[di],-1 ;Set new end of list flag
- mov ax,di ;Save end pointer to list
- add ax,2 ;Make room for the end flag.
- mov cs:[aliaslist_end],ax
- sub di,bp ;Compute size of entry
- mov es:[bp],di ;Put size over old end flag.
- inc cs:[file_linecount] ;Point counter to next line.
- setalias_exit:
- clc
- setalias_exit1:
- pop es ;Restore ptr to installed seg
- pop bp
- ret
- setalias_full:
- mov dx,offset errmsg9 ;Alias list too large msg.
- jmp short setalias_error
- setalias_notnfil:
- mov dx,offset errmsg13 ;Alias not in list.
- setalias_error:
- stc
- jmp short setalias_exit1
- setalias endp
-
- ;-----------------------------------------------------------------------------
- ; CAPIT - Converts char in AL to upper case
- ;-----------------------------------------------------------------------------
- capit proc near
- cmp al,"a" ; match when searched for in
- jb capit_exit ; the environment block.
- cmp al,"z"
- ja capit_exit
- and al,0dfh ;Make character uppercase.
- capit_exit:
- ret
- capit endp
- ;-----------------------------------------------------------------------------
- ; LOADALIASFILE loads a file containing a list of alias commands.
- ; Entry: DS:SI - pointer to the name of the file to open
- ; exit: CX - size of the file in bytes
- ; CF - clear if successful
- ;-----------------------------------------------------------------------------
- loadaliasfile proc near
- assume ds:nothing,es:nothing
- xor bl,bl
- call scanline ;Find 1st char of filename.
- mov dx,si ;Copy filename pointer
- inc bl ;Find end of filename
- call scanline
- mov byte ptr [si-1],0 ;Make filename ASCIIZ.
- dec dx
- mov ax,3d00h ;Open file (Read only)
- int 21h
- jc loadfile_error
- mov bx,ax ;Copy file handle
- ;
- ;Save the name of the file for error messages.
- ;
- push si
- push es
- mov di,offset filenam_field
- push cs
- pop es
- mov si,dx
- loadfile_1:
- lodsb
- stosb
- or al,al
- jne loadfile_1
- mov byte ptr es:[di-1],"0" ;Terminate string with 0.
- pop es
- pop si
- ;
- ;Open file and read contents into file buffer.
- ;
- mov ah,3fh ;Read alias file
- xor dx,dx ;Point to base of file buffer.
- mov cx,cs:[filebuf_size] ;Get size of file buffer.
- shl cx,1 ;Convert to bytes
- shl cx,1
- shl cx,1
- shl cx,1
- int 21h
- mov si,ax
- mov byte ptr ds:[si],13 ;Append a CR to end of file.
- mov cx,ax ;Save new file size
- xor si,si ;Reset file pointer.
- mov ah,3eh ;Close file.
- int 21h
- mov cs:[file_linecount],1 ;Reset line counter.
- loadfile_exit:
- clc
- loadfile_exit1:
- ret
- loadfile_error:
- stc
- mov dx,offset errmsg6 ;Bad filename specified.
- jmp short loadfile_exit1
- loadaliasfile endp
- ;-----------------------------------------------------------------------------
- ; LISTALIAS prints status info followed by the alias list to screen.
- ; Entry: ES - segment of the installed code
- ;-----------------------------------------------------------------------------
- listalias proc near
- assume ds:nothing,es:nothing
- push ds
- ;
- ;Print Command stack size and amount of alias buffer space remaining
- ;
- mov dx,offset infomsg2 ;Print size of command stack
- call printmsg
- mov ax,es:[cmdstack_size] ;Get size of command stack
- cwd
- mov bx,32
- div bx
- call hex2asc ;Print size
- mov dx,offset infomsg3 ;Print min cmd length
- call printmsg
- xor ax,ax
- mov al,es:[minlength] ;Get min cmd length to stack
- call hex2asc ;Print length
- mov dx,offset infomsg4 ;Print label to buffer size
- call printmsg
-
- lds si,es:[aliaslist_ptr] ;Get pointer to alias list
- xor dx,dx
- listalias_1:
- cmp word ptr [si],-1 ;Scan through alias list to
- je listalias_2 ; find the end of the list.
- add si,[si] ;Point to next entry
- mov dh,1
- jmp short listalias_1
- listalias_2:
- push dx
- mov ax,es:[aliaslist_size] ;Get offset to end of buffer
- sub ax,si ;Subtract end of alias list
- sub ax,2 ;Correct for end pointer
- call hex2asc ;Print size
- mov dx,offset infomsg5 ;Indicate if alias translation
- call printmsg ; is enabled or disabled
- mov dx,offset infomsg5d ;Disabled message
- cmp byte ptr es:[chk_alias],0 ;See if alias enabled
- je listalias_3
- mov dx,offset infomsg5e ;Enabled message
- listalias_3:
- call printmsg
- pop dx
-
- test dh,1 ;See if any aliases found
- je listalias_4 ;If no aliases, skip
- mov si,offset infomsg7+2 ;Kluge to erase comment
- mov word ptr cs:[si],2020h ; chars from header.
- call listalias1
- listalias_4:
- mov dx,offset infomsg8 ;Print pointer to help msg
- call printmsgcr
- pop ds
- ret
- listalias endp
- ;-----------------------------------------------------------------------------
- ; LISTALIAS1 prints the alias list to screen.
- ; Entry: ES - segment of the installed code
- ;-----------------------------------------------------------------------------
- listalias1 proc near
- assume ds:nothing,es:nothing
- push ds
- mov dx,offset infomsg7 ;Print header
- call printmsgcr
- xor cx,cx ;Clear CX
- lds si,es:[aliaslist_ptr] ;Get pointer to alias list
- listalias1_1:
- mov bx,si ;Save pointer to entry.
- cmp byte ptr [si+2],0 ;See if key definition
- jne listalias1_2 ;If so, skip entry
- add si,[bx]
- jmp short listalias1_3
- listalias1_2:
- call printtab
- add si,4 ;Point SI to alias string
- mov cl,[bx+2] ;Get length of alias
- call print_string ;Print alias to screen
- call printtab
- call printtab
- mov cl,[bx+3] ;Get length of command
- call print_string ;Print command to screen
- mov dx,offset endmsg ;Append carriage return to
- call printmsg ; advance to next line.
- listalias1_3:
- cmp word ptr [si],-1 ;Check for end of list. SI
- jne listalias1_1 ; points to the next entry.
- listalias1_exit:
- pop ds
- clc
- ret
- listalias1 endp
- ;-----------------------------------------------------------------------------
- ; PRINTTAB prints a TAB character to the screen.
- ; Entry: ES - segment of the installed code
- ;-----------------------------------------------------------------------------
- printtab proc near
- assume ds:nothing,es:nothing
- mov al,9 ;Print TAB character
- call print_char
- ret
- printtab endp
-
- ;-----------------------------------------------------------------------------
- ; ENABLEALIAS enables alias translation.
- ; Entry: ES - segment of the installed code
- ;-----------------------------------------------------------------------------
- enablealias proc near
- assume ds:nothing,es:nothing
- mov byte ptr es:[chk_alias],1 ;Enable alias
- clc
- ret
- enablealias endp
-
- ;-----------------------------------------------------------------------------
- ; DISABLEALIAS disables alias translation.
- ; Entry: ES - segment of the installed code
- ;-----------------------------------------------------------------------------
- disablealias proc near
- assume ds:nothing,es:nothing
- mov byte ptr es:[chk_alias],0 ;Disable alias
- clc
- ret
- disablealias endp
-
- ;-----------------------------------------------------------------------------
- ; INSCURSOR Toggles the insert cursor to underline/block
- ; Entry: ES - segment of the installed code
- ;-----------------------------------------------------------------------------
- inscursor proc near
- assume ds:nothing,es:nothing
- xor byte ptr es:[insert_cursor],1 ;Toggle block flag
- clc
- ret
- inscursor endp
-
- ;-----------------------------------------------------------------------------
- ; REMOVE uninstalls the installed program from memory.
- ;-----------------------------------------------------------------------------
- remove proc near
- assume ds:nothing,es:nothing
- push ds
- mov dx,offset errmsg1 ;Not installed msg
- cmp cs:[alrdy_installed],0 ;See if installed
- je remove_exit ;Not installed, error
-
- mov cx,es ;Get installed segment
- mov ax,3521h ;Get DOS vector
- int 21h
- mov ax,es ;Check to make sure DOS
- cmp ax,cx ; vector not modified.
- jne remove_error
-
- mov ax,352fh ;Get MUX vector
- int 21h
- mov ax,es ;Check to make sure MUX
- cmp ax,cx ; vector not modified.
- jne remove_error
-
- lds dx,es:[int2fh] ;Get old interrupt 2F vector
- mov ax,252fh ;Set interrupt
- int 21h
-
- lds dx,es:[int21h] ;Get old interrupt 21 vector
- mov ax,2521h ;Set interrupt
- int 21h
-
- mov cx,es:[env_segment]
- mov ah,49h ;Free code block
- int 21h
- mov es,cx ;Free environment block
- mov ah,49h
- int 21h
- mov dx,offset infomsg1 ;Indicate uninstalled.
- mov byte ptr filenam_field,0 ;Clear filename field
- remove_exit:
- stc
- pop ds
- remove_exit1: ret
- remove_error:
- mov dx,offset errmsg3 ;Can't remove error msg
- jmp short remove_exit
-
- remove endp
-
- ;-----------------------------------------------------------------------------
- ; COMMENT_LINE allows comments in the alias file by skipping to the next
- ; carriage return.
- ; Entry: SI - pointer to ASCII string
- ; CX - file length
- ;-----------------------------------------------------------------------------
- comment_line proc near
- assume ds:nothing,es:nothing
- comment_loop:
- push es
- push ds
- pop es
- mov di,si ;Copy file pointer
- mov al,13 ;Scan for carriage return.
- repne scasb
- inc cs:[file_linecount] ;Inc file line counter.
- mov si,di ;Restore file pointer.
- pop es
- clc
- ret
- comment_line endp
-
- ;-----------------------------------------------------------------------------
- ; ASC2BIN - converts an ASCII number of the command line to hex.
- ; Entry: DS:SI - pointer to ASCII number
- ;-----------------------------------------------------------------------------
- asc2bin proc near
- push bx
- xor bl,bl
- call scanline ;Find next character.
- mov di,offset errmsg5 ;Bad number message
- jc asc_error ;If no number found, error
- mov bl,al ;Copy first digit.
- xor ax,ax ;Clear out sum
- xor bh,bh ;Clear high byte for word adds
- asc_loop:
- cmp bl," " ;If space, assume end of
- jbe asc_exit ; number.
- cmp bl,"]" ;Exit if closing bracket
- je asc_exit ; encountered
- sub bl,"0" ;Check for valid number then
- jb asc_error ; convert to binary.
- cmp bl,9
- ja asc_error
- mov dx,10 ;DX holds base multiplier
- mul dx ;Shift over current number
- jc asc_overflow ;If overflow, indicate error
- add ax,bx ;Add new digit to sum.
- jcxz asc_exit ;If end of file, exit.
- mov bl,ds:[si] ;Get next ASCII character
- inc si ;Point to next character
- dec cx ;Dec file size counter
- jmp short asc_loop ;Go back for more
- asc_exit:
- clc ;Clear error flag.
- asc_exit1:
- pop bx
- ret
- asc_overflow:
- mov di,offset errmsg12 ;Number too large message.
- asc_error:
- mov dx,di ;Copy message pointer.
- stc ;Set error flag.
- jmp short asc_exit1
- asc2bin endp
- ;-----------------------------------------------------------------------------
- ; SCANLINE performs the same function as SCAN4CHAR but keeps track of the
- ; carriage returns.
- ; Entry: SI - pointer to ASCII string
- ; BL - 0 = find next char, 1 = find next space
- ; CX - file length
- ; Exit: AL - first nonspace character
- ; CF - set if carriage return found
- ;-----------------------------------------------------------------------------
- scanline proc near
- call scan4char ;Find the next char.
- jnc scanline_exit
- inc cs:[file_linecount] ;Point to next line.
- stc
- scanline_exit:
- ret
- scanline endp
- even
- end_of_code = $
- code ends
-
- end main
-